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

Safe HaskellNone
LanguageHaskell2010

Graphics.Vulkan.Marshal.Proc

Contents

Description

This module allows to load vulkan symbols at runtime.

It is based on Vulkan API function vkGetInstanceProcAddr that is a part of Vulkan core 1.0. Also, have a look at Vulkan loader page to see other reasons to load symbols manually.

All FFI functions are present in two variants: xxxUnsafe and xxxSafe, the names stand for foreign import unsafe xxx foreign import safe xxx respectively. In particular, that does not mean that vkGetXxxProcSafe function cannot fail; it does error if the symbol is not present in the implementation!

Synopsis

Documentation

class VulkanProc proc where Source #

Some of the vulkan functions defined in vulkan extensions are not available at the program linking time. These functions should be discovered at runtime. Vulkan api provides special functions for this, called vkGetInstanceProcAddr and vkGetDeviceProcAddr. This class provides a simpler discovery mechanism based on that function. For example, you can get vkCreateDebugReportCallbackEXT function as follows:

vkGetInstanceProc @VkCreateDebugReportCallbackEXT vkInstance

Associated Types

type VkProcType proc Source #

Haskell signature for the vulkan function

Methods

vkProcSymbol :: CString Source #

Name of the vulkan function

unwrapVkProcPtrUnsafe :: FunPtr (VkProcType proc) -> VkProcType proc Source #

Convert C function pointer to an ordinary haskell function. Use unsafe FFI (foreign import unsafe "dynamic" ...).

unwrapVkProcPtrSafe :: FunPtr (VkProcType proc) -> VkProcType proc Source #

Convert C function pointer to an ordinary haskell function. Use safe FFI (foreign import safe "dynamic" ...).

vkGetInstanceProc :: forall proc. VulkanProc proc => VkInstance -> IO (VkProcType proc) Source #

An alternative to vkGetInstanceProcAddr with type inference and protection against typos.

Note, this is an unsafe function; it does not check if the result of vkGetInstanceProcAddr is a null function pointer.

vkGetInstanceProcUnsafe :: forall proc. VulkanProc proc => VkInstance -> IO (VkProcType proc) Source #

An alternative to vkGetInstanceProcAddr with type inference and protection against typos.

Note, this is an unsafe function; it does not check if the result of vkGetInstanceProcAddr is a null function pointer.

vkGetInstanceProcSafe :: forall proc. VulkanProc proc => VkInstance -> IO (VkProcType proc) Source #

An alternative to vkGetInstanceProcAddr with type inference and protection against typos.

Note, this is an unsafe function; it does not check if the result of vkGetInstanceProcAddr is a null function pointer.

vkLookupInstanceProc :: forall proc. VulkanProc proc => VkInstance -> IO (Maybe (VkProcType proc)) Source #

An alternative to vkGetInstanceProcAddr with type inference and protection against typos.

vkLookupInstanceProcUnsafe :: forall proc. VulkanProc proc => VkInstance -> IO (Maybe (VkProcType proc)) Source #

An alternative to vkGetInstanceProcAddr with type inference and protection against typos.

vkLookupInstanceProcSafe :: forall proc. VulkanProc proc => VkInstance -> IO (Maybe (VkProcType proc)) Source #

An alternative to vkGetInstanceProcAddr with type inference and protection against typos.

vkGetDeviceProc :: forall proc. VulkanProc proc => VkDevice -> IO (VkProcType proc) Source #

An alternative to vkGetDeviceProcAddr with type inference and protection against typos.

Note, this is an unsafe function; it does not check if the result of vkGetInstanceProcAddr is a null function pointer.

vkGetDeviceProcUnsafe :: forall proc. VulkanProc proc => VkDevice -> IO (VkProcType proc) Source #

An alternative to vkGetDeviceProcAddr with type inference and protection against typos.

Note, this is an unsafe function; it does not check if the result of vkGetInstanceProcAddr is a null function pointer.

vkGetDeviceProcSafe :: forall proc. VulkanProc proc => VkDevice -> IO (VkProcType proc) Source #

An alternative to vkGetDeviceProcAddr with type inference and protection against typos.

Note, this is an unsafe function; it does not check if the result of vkGetInstanceProcAddr is a null function pointer.

vkLookupDeviceProc :: forall proc. VulkanProc proc => VkDevice -> IO (Maybe (VkProcType proc)) Source #

An alternative to vkGetDeviceProcAddr with type inference and protection against typos.

vkLookupDeviceProcUnsafe :: forall proc. VulkanProc proc => VkDevice -> IO (Maybe (VkProcType proc)) Source #

An alternative to vkGetDeviceProcAddr with type inference and protection against typos.

vkLookupDeviceProcSafe :: forall proc. VulkanProc proc => VkDevice -> IO (Maybe (VkProcType proc)) Source #

An alternative to vkGetDeviceProcAddr with type inference and protection against typos.

vkGetProc :: forall proc. VulkanProc proc => IO (VkProcType proc) Source #

Locate Vulkan symbol dynamically at runtime using platform-dependent machinery, such as dlsym or GetProcAddress. This function throws an error on failure.

Consider using vkGetDeviceProc or vkGetInstanceProc for loading a symbol, because they can return a more optimized version of a function. Also note, you are likely not able to lookup an extension funcion using vkGetProc, because a corresponding symbol is simply not present in the vulkan loader library.

vkGetProcUnsafe :: forall proc. VulkanProc proc => IO (VkProcType proc) Source #

Locate Vulkan symbol dynamically at runtime using platform-dependent machinery, such as dlsym or GetProcAddress. This function throws an error on failure.

Consider using vkGetDeviceProc or vkGetInstanceProc for loading a symbol, because they can return a more optimized version of a function. Also note, you are likely not able to lookup an extension funcion using vkGetProc, because a corresponding symbol is simply not present in the vulkan loader library.

vkGetProcSafe :: forall proc. VulkanProc proc => IO (VkProcType proc) Source #

Locate Vulkan symbol dynamically at runtime using platform-dependent machinery, such as dlsym or GetProcAddress. This function throws an error on failure.

Consider using vkGetDeviceProc or vkGetInstanceProc for loading a symbol, because they can return a more optimized version of a function. Also note, you are likely not able to lookup an extension funcion using vkGetProc, because a corresponding symbol is simply not present in the vulkan loader library.

vkLookupProc :: forall proc. VulkanProc proc => IO (Maybe (VkProcType proc)) Source #

Locate Vulkan symbol dynamically at runtime using platform-dependent machinery, such as dlsym or GetProcAddress. This function returns Nothing on failure ignoring an error message.

Consider using vkGetDeviceProc or vkGetInstanceProc for loading a symbol, because they can return a more optimized version of a function. Also note, you are likely not able to lookup an extension funcion using vkLookupProc, because a corresponding symbol is simply not present in the vulkan loader library.

vkLookupProcUnsafe :: forall proc. VulkanProc proc => IO (Maybe (VkProcType proc)) Source #

Locate Vulkan symbol dynamically at runtime using platform-dependent machinery, such as dlsym or GetProcAddress. This function returns Nothing on failure ignoring an error message.

Consider using vkGetDeviceProc or vkGetInstanceProc for loading a symbol, because they can return a more optimized version of a function. Also note, you are likely not able to lookup an extension funcion using vkLookupProc, because a corresponding symbol is simply not present in the vulkan loader library.

vkLookupProcSafe :: forall proc. VulkanProc proc => IO (Maybe (VkProcType proc)) Source #

Locate Vulkan symbol dynamically at runtime using platform-dependent machinery, such as dlsym or GetProcAddress. This function returns Nothing on failure ignoring an error message.

Consider using vkLookupDeviceProc or vkLookupInstanceProc for loading a symbol, because they can return a more optimized version of a function. Also note, you are likely not able to lookup an extension funcion using vkLookupProc, because a corresponding symbol is simply not present in the vulkan loader library.

Re-export Ptr

data FunPtr a :: * -> * #

A value of type FunPtr a is a pointer to a function callable from foreign code. The type a will normally be a foreign type, a function type with zero or more arguments where

A value of type FunPtr a may be a pointer to a foreign function, either returned by another foreign function or imported with a a static address import like

foreign import ccall "stdlib.h &free"
  p_free :: FunPtr (Ptr a -> IO ())

or a pointer to a Haskell function created using a wrapper stub declared to produce a FunPtr of the correct type. For example:

type Compare = Int -> Int -> Bool
foreign import ccall "wrapper"
  mkCompare :: Compare -> IO (FunPtr Compare)

Calls to wrapper stubs like mkCompare allocate storage, which should be released with freeHaskellFunPtr when no longer required.

To convert FunPtr values to corresponding Haskell functions, one can define a dynamic stub for the specific foreign type, e.g.

type IntFunction = CInt -> IO ()
foreign import ccall "dynamic"
  mkFun :: FunPtr IntFunction -> IntFunction

Instances

Eq (FunPtr a) 

Methods

(==) :: FunPtr a -> FunPtr a -> Bool #

(/=) :: FunPtr a -> FunPtr a -> Bool #

Ord (FunPtr a) 

Methods

compare :: FunPtr a -> FunPtr a -> Ordering #

(<) :: FunPtr a -> FunPtr a -> Bool #

(<=) :: FunPtr a -> FunPtr a -> Bool #

(>) :: FunPtr a -> FunPtr a -> Bool #

(>=) :: FunPtr a -> FunPtr a -> Bool #

max :: FunPtr a -> FunPtr a -> FunPtr a #

min :: FunPtr a -> FunPtr a -> FunPtr a #

Show (FunPtr a) 

Methods

showsPrec :: Int -> FunPtr a -> ShowS #

show :: FunPtr a -> String #

showList :: [FunPtr a] -> ShowS #

Storable (FunPtr a) 

Methods

sizeOf :: FunPtr a -> Int #

alignment :: FunPtr a -> Int #

peekElemOff :: Ptr (FunPtr a) -> Int -> IO (FunPtr a) #

pokeElemOff :: Ptr (FunPtr a) -> Int -> FunPtr a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (FunPtr a) #

pokeByteOff :: Ptr b -> Int -> FunPtr a -> IO () #

peek :: Ptr (FunPtr a) -> IO (FunPtr a) #

poke :: Ptr (FunPtr a) -> FunPtr a -> IO () #

nullFunPtr :: FunPtr a #

The constant nullFunPtr contains a distinguished value of FunPtr that is not associated with a valid memory location.