vulkan-api-1.4.0.0: Low-level low-overhead vulkan api bindings
Safe HaskellNone
LanguageHaskell2010

Graphics.Vulkan

Description

This module is not part of auto-generated code based on vk.xml. Instead, it is hand-written to aggregate all generated code.

Synopsis

Documentation

VK_API_VERSION
// DEPRECATED: This define has been removed. Specific version defines (e.g. VK_API_VERSION_1_0), or the VK_MAKE_VERSION macro, should be used instead.
//#define VK_API_VERSION VK_MAKE_VERSION(1, 0, 0) // Patch version should always be set to 0

type VK_API_VERSION_1_0 = 4194304 Source #

pattern VK_API_VERSION_1_0 :: (Num a, Eq a) => a Source #

// Vulkan 1.0 version number
#define VK_API_VERSION_1_0 VK_MAKE_VERSION(1, 0, 0)// Patch version should always be set to 0

type VK_API_VERSION_1_1 = 4198400 Source #

pattern VK_API_VERSION_1_1 :: (Num a, Eq a) => a Source #

// Vulkan 1.1 version number
#define VK_API_VERSION_1_1 VK_MAKE_VERSION(1, 1, 0)// Patch version should always be set to 0

type VK_API_VERSION_1_2 = 4202496 Source #

pattern VK_API_VERSION_1_2 :: (Num a, Eq a) => a Source #

// Vulkan 1.2 version number
#define VK_API_VERSION_1_2 VK_MAKE_VERSION(1, 2, 0)// Patch version should always be set to 0

data Ptr a #

A value of type Ptr a represents a pointer to an object, or an array of objects, which may be marshalled to or from Haskell values of type a.

The type a will often be an instance of class Storable which provides the marshalling operations. However this is not essential, and you can provide your own operations to access the pointer. For example you might write small foreign functions to get or set the fields of a C struct.

Instances

Instances details
VulkanPtr Ptr Source # 
Instance details

Defined in Graphics.Vulkan.Marshal

Methods

vkNullPtr :: Ptr a Source #

Generic1 (URec (Ptr ()) :: k -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (URec (Ptr ())) :: k -> Type #

Methods

from1 :: forall (a :: k0). URec (Ptr ()) a -> Rep1 (URec (Ptr ())) a #

to1 :: forall (a :: k0). Rep1 (URec (Ptr ())) a -> URec (Ptr ()) a #

Eq (Ptr a)

Since: base-2.1

Instance details

Defined in GHC.Ptr

Methods

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

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

Ord (Ptr a)

Since: base-2.1

Instance details

Defined in GHC.Ptr

Methods

compare :: Ptr a -> Ptr a -> Ordering #

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

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

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

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

max :: Ptr a -> Ptr a -> Ptr a #

min :: Ptr a -> Ptr a -> Ptr a #

Show (Ptr a)

Since: base-2.1

Instance details

Defined in GHC.Ptr

Methods

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

show :: Ptr a -> String #

showList :: [Ptr a] -> ShowS #

Foldable (UAddr :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => UAddr m -> m #

foldMap :: Monoid m => (a -> m) -> UAddr a -> m #

foldMap' :: Monoid m => (a -> m) -> UAddr a -> m #

foldr :: (a -> b -> b) -> b -> UAddr a -> b #

foldr' :: (a -> b -> b) -> b -> UAddr a -> b #

foldl :: (b -> a -> b) -> b -> UAddr a -> b #

foldl' :: (b -> a -> b) -> b -> UAddr a -> b #

foldr1 :: (a -> a -> a) -> UAddr a -> a #

foldl1 :: (a -> a -> a) -> UAddr a -> a #

toList :: UAddr a -> [a] #

null :: UAddr a -> Bool #

length :: UAddr a -> Int #

elem :: Eq a => a -> UAddr a -> Bool #

maximum :: Ord a => UAddr a -> a #

minimum :: Ord a => UAddr a -> a #

sum :: Num a => UAddr a -> a #

product :: Num a => UAddr a -> a #

Traversable (UAddr :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UAddr a -> f (UAddr b) #

sequenceA :: Applicative f => UAddr (f a) -> f (UAddr a) #

mapM :: Monad m => (a -> m b) -> UAddr a -> m (UAddr b) #

sequence :: Monad m => UAddr (m a) -> m (UAddr a) #

Storable (Ptr a)

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Ptr a -> Int #

alignment :: Ptr a -> Int #

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

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

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

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

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

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

Functor (URec (Ptr ()) :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

fmap :: (a -> b) -> URec (Ptr ()) a -> URec (Ptr ()) b #

(<$) :: a -> URec (Ptr ()) b -> URec (Ptr ()) a #

Eq (URec (Ptr ()) p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

(==) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool #

(/=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool #

Ord (URec (Ptr ()) p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

compare :: URec (Ptr ()) p -> URec (Ptr ()) p -> Ordering #

(<) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool #

(<=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool #

(>) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool #

(>=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool #

max :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p #

min :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p #

Generic (URec (Ptr ()) p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec (Ptr ()) p) :: Type -> Type #

Methods

from :: URec (Ptr ()) p -> Rep (URec (Ptr ()) p) x #

to :: Rep (URec (Ptr ()) p) x -> URec (Ptr ()) p #

data URec (Ptr ()) (p :: k)

Used for marking occurrences of Addr#

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

data URec (Ptr ()) (p :: k) = UAddr {}
type Rep1 (URec (Ptr ()) :: k -> Type) 
Instance details

Defined in GHC.Generics

type Rep1 (URec (Ptr ()) :: k -> Type) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UAddr" 'PrefixI 'True) (S1 ('MetaSel ('Just "uAddr#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UAddr :: k -> Type)))
type Rep (URec (Ptr ()) p) 
Instance details

Defined in GHC.Generics

type Rep (URec (Ptr ()) p) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UAddr" 'PrefixI 'True) (S1 ('MetaSel ('Just "uAddr#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UAddr :: Type -> Type)))
VK_DEFINE_HANDLE

Dispatchable handles are represented as Ptr

#define VK_DEFINE_HANDLE(object) typedef struct object##_T* object;

newtype VkPtr a Source #

VK_DEFINE_NON_DISPATCHABLE_HANDLE

Non-dispatchable handles are represented as VkPtr

Represented as Word64

#if !defined(VK_DEFINE_NON_DISPATCHABLE_HANDLE)
#if defined(__LP64__) || defined(_WIN64) || (defined(__x86_64__) && !defined(__ILP32__) ) || defined(_M_X64) || defined(__ia64) || defined (_M_IA64) || defined(__aarch64__) || defined(__powerpc64__)
        #define VK_DEFINE_NON_DISPATCHABLE_HANDLE(object) typedef struct object##_T *object;
#else
        #define VK_DEFINE_NON_DISPATCHABLE_HANDLE(object) typedef uint64_t object;
#endif
#endif

Constructors

VkPtr Word64 

Instances

Instances details
VulkanPtr VkPtr Source # 
Instance details

Defined in Graphics.Vulkan.Marshal

Methods

vkNullPtr :: VkPtr a Source #

Eq (VkPtr a) Source # 
Instance details

Defined in Graphics.Vulkan.Marshal

Methods

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

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

Ord (VkPtr a) Source # 
Instance details

Defined in Graphics.Vulkan.Marshal

Methods

compare :: VkPtr a -> VkPtr a -> Ordering #

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

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

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

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

max :: VkPtr a -> VkPtr a -> VkPtr a #

min :: VkPtr a -> VkPtr a -> VkPtr a #

Show (VkPtr a) Source # 
Instance details

Defined in Graphics.Vulkan.Marshal

Methods

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

show :: VkPtr a -> String #

showList :: [VkPtr a] -> ShowS #

Storable (VkPtr a) Source # 
Instance details

Defined in Graphics.Vulkan.Marshal

Methods

sizeOf :: VkPtr a -> Int #

alignment :: VkPtr a -> Int #

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

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

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

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

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

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

VK_DEFINE_NON_DISPATCHABLE_HANDLE

Non-dispatchable handles are represented as VkPtr

#if !defined(VK_DEFINE_NON_DISPATCHABLE_HANDLE)
#if defined(__LP64__) || defined(_WIN64) || (defined(__x86_64__) && !defined(__ILP32__) ) || defined(_M_X64) || defined(__ia64) || defined (_M_IA64) || defined(__aarch64__) || defined(__powerpc64__)
        #define VK_DEFINE_NON_DISPATCHABLE_HANDLE(object) typedef struct object##_T *object;
#else
        #define VK_DEFINE_NON_DISPATCHABLE_HANDLE(object) typedef uint64_t object;
#endif
#endif

pattern VK_HEADER_VERSION :: (Num a, Eq a) => a Source #

// Version of this file
#define VK_HEADER_VERSION 152

_VK_HEADER_VERSION_COMPLETE :: (Bits a, Num a) => a Source #

// Complete version of this file
#define VK_HEADER_VERSION_COMPLETE VK_MAKE_VERSION(1, 2, VK_HEADER_VERSION)

_VK_MAKE_VERSION :: Bits a => a -> a -> a -> a Source #

#define VK_MAKE_VERSION(major, minor, patch) --   >     ((((uint32_t)(major)) << 22) | (((uint32_t)(minor)) << 12) | ((uint32_t)(patch)))

class VulkanPtr ptr where Source #

Unify dispatchable and non-dispatchable vulkan pointer types.

Dispatchable handles are represented as Ptr.

Non-dispatchable handles are represented as VkPtr.

Methods

vkNullPtr :: ptr a Source #

Instances

Instances details
VulkanPtr Ptr Source # 
Instance details

Defined in Graphics.Vulkan.Marshal

Methods

vkNullPtr :: Ptr a Source #

VulkanPtr VkPtr Source # 
Instance details

Defined in Graphics.Vulkan.Marshal

Methods

vkNullPtr :: VkPtr a Source #

pattern VK_NULL_HANDLE :: (Eq (ptr a), VulkanPtr ptr) => ptr a Source #

#define VK_NULL_HANDLE 0

_VK_VERSION_MAJOR :: Bits a => a -> a Source #

#define VK_VERSION_MAJOR(version) ((uint32_t)(version) >> 22)

_VK_VERSION_MINOR :: (Bits a, Num a) => a -> a Source #

#define VK_VERSION_MINOR(version) (((uint32_t)(version) >> 12) & 0x3ff)

_VK_VERSION_PATCH :: (Bits a, Num a) => a -> a Source #

#define VK_VERSION_PATCH(version) ((uint32_t)(version) & 0xfff)

type PFN_vkAllocationFunction = FunPtr HS_vkAllocationFunction Source #

typedef void* (VKAPI_PTR *PFN_vkAllocationFunction)(
    void*                                       pUserData,
    size_t                                      size,
    size_t                                      alignment,
    VkSystemAllocationScope                     allocationScope);

newVkAllocationFunction :: HS_vkAllocationFunction -> IO PFN_vkAllocationFunction Source #

Wrap haskell function into C-callable FunPtr. Note, you need to free resources after using it.

type PFN_vkDebugReportCallbackEXT = FunPtr HS_vkDebugReportCallbackEXT Source #

typedef VkBool32 (VKAPI_PTR *PFN_vkDebugReportCallbackEXT)(
    VkDebugReportFlagsEXT                       flags,
    VkDebugReportObjectTypeEXT                  objectType,
    uint64_t                                    object,
    size_t                                      location,
    int32_t                                     messageCode,
    const char*                                 pLayerPrefix,
    const char*                                 pMessage,
    void*                                       pUserData);

newVkDebugReportCallbackEXT :: HS_vkDebugReportCallbackEXT -> IO PFN_vkDebugReportCallbackEXT Source #

Wrap haskell function into C-callable FunPtr. Note, you need to free resources after using it.

type PFN_vkDebugUtilsMessengerCallbackEXT = FunPtr HS_vkDebugUtilsMessengerCallbackEXT Source #

typedef VkBool32 (VKAPI_PTR *PFN_vkDebugUtilsMessengerCallbackEXT)(
    VkDebugUtilsMessageSeverityFlagBitsEXT           messageSeverity,
    VkDebugUtilsMessageTypeFlagsEXT                  messageTypes,
    const VkDebugUtilsMessengerCallbackDataEXT*      pCallbackData,
    void*                                            pUserData);

newVkDebugUtilsMessengerCallbackEXT :: HS_vkDebugUtilsMessengerCallbackEXT -> IO PFN_vkDebugUtilsMessengerCallbackEXT Source #

Wrap haskell function into C-callable FunPtr. Note, you need to free resources after using it.

type PFN_vkFreeFunction = FunPtr HS_vkFreeFunction Source #

typedef void (VKAPI_PTR *PFN_vkFreeFunction)(
    void*                                       pUserData,
    void*                                       pMemory);

newVkFreeFunction :: HS_vkFreeFunction -> IO PFN_vkFreeFunction Source #

Wrap haskell function into C-callable FunPtr. Note, you need to free resources after using it.

type PFN_vkInternalAllocationNotification = FunPtr HS_vkInternalAllocationNotification Source #

typedef void (VKAPI_PTR *PFN_vkInternalAllocationNotification)(
    void*                                       pUserData,
    size_t                                      size,
    VkInternalAllocationType                    allocationType,
    VkSystemAllocationScope                     allocationScope);

newVkInternalAllocationNotification :: HS_vkInternalAllocationNotification -> IO PFN_vkInternalAllocationNotification Source #

Wrap haskell function into C-callable FunPtr. Note, you need to free resources after using it.

type PFN_vkInternalFreeNotification = FunPtr HS_vkInternalFreeNotification Source #

typedef void (VKAPI_PTR *PFN_vkInternalFreeNotification)(
    void*                                       pUserData,
    size_t                                      size,
    VkInternalAllocationType                    allocationType,
    VkSystemAllocationScope                     allocationScope);

newVkInternalFreeNotification :: HS_vkInternalFreeNotification -> IO PFN_vkInternalFreeNotification Source #

Wrap haskell function into C-callable FunPtr. Note, you need to free resources after using it.

type PFN_vkReallocationFunction = FunPtr HS_vkReallocationFunction Source #

typedef void* (VKAPI_PTR *PFN_vkReallocationFunction)(
    void*                                       pUserData,
    void*                                       pOriginal,
    size_t                                      size,
    size_t                                      alignment,
    VkSystemAllocationScope                     allocationScope);

newVkReallocationFunction :: HS_vkReallocationFunction -> IO PFN_vkReallocationFunction Source #

Wrap haskell function into C-callable FunPtr. Note, you need to free resources after using it.

type PFN_vkVoidFunction = FunPtr HS_vkVoidFunction Source #

typedef void (VKAPI_PTR *PFN_vkVoidFunction)(void);

newVkVoidFunction :: HS_vkVoidFunction -> IO PFN_vkVoidFunction Source #

Wrap haskell function into C-callable FunPtr. Note, you need to free resources after using it.

data VkAccelerationStructureKHR_T Source #

Opaque data type referenced by VkAccelerationStructureKHR

data VkAccelerationStructureNV_T Source #

Opaque data type referenced by VkAccelerationStructureNV

data VkBuffer_T Source #

Opaque data type referenced by VkBuffer

data VkBufferView_T Source #

Opaque data type referenced by VkBufferView

data VkCommandBuffer_T Source #

Opaque data type referenced by VkCommandBuffer

data VkCommandPool_T Source #

Opaque data type referenced by VkCommandPool

data VkDebugReportCallbackEXT_T Source #

Opaque data type referenced by VkDebugReportCallbackEXT

data VkDebugUtilsMessengerEXT_T Source #

Opaque data type referenced by VkDebugUtilsMessengerEXT

data VkDeferredOperationKHR_T Source #

Opaque data type referenced by VkDeferredOperationKHR

data VkDescriptorPool_T Source #

Opaque data type referenced by VkDescriptorPool

data VkDescriptorSet_T Source #

Opaque data type referenced by VkDescriptorSet

data VkDescriptorSetLayout_T Source #

Opaque data type referenced by VkDescriptorSetLayout

data VkDescriptorUpdateTemplate_T Source #

Opaque data type referenced by VkDescriptorUpdateTemplate

data VkDescriptorUpdateTemplateKHR_T Source #

Opaque data type referenced by VkDescriptorUpdateTemplateKHR

data VkDevice_T Source #

Opaque data type referenced by VkDevice

data VkDeviceMemory_T Source #

Opaque data type referenced by VkDeviceMemory

data VkDisplayKHR_T Source #

Opaque data type referenced by VkDisplayKHR

data VkDisplayModeKHR_T Source #

Opaque data type referenced by VkDisplayModeKHR

data VkEvent_T Source #

Opaque data type referenced by VkEvent

data VkFence_T Source #

Opaque data type referenced by VkFence

data VkFramebuffer_T Source #

Opaque data type referenced by VkFramebuffer

data VkImage_T Source #

Opaque data type referenced by VkImage

data VkImageView_T Source #

Opaque data type referenced by VkImageView

data VkIndirectCommandsLayoutNV_T Source #

Opaque data type referenced by VkIndirectCommandsLayoutNV

data VkInstance_T Source #

Opaque data type referenced by VkInstance

data VkPerformanceConfigurationINTEL_T Source #

Opaque data type referenced by VkPerformanceConfigurationINTEL

data VkPhysicalDevice_T Source #

Opaque data type referenced by VkPhysicalDevice

data VkPipeline_T Source #

Opaque data type referenced by VkPipeline

data VkPipelineCache_T Source #

Opaque data type referenced by VkPipelineCache

data VkPipelineLayout_T Source #

Opaque data type referenced by VkPipelineLayout

data VkPrivateDataSlotEXT_T Source #

Opaque data type referenced by VkPrivateDataSlotEXT

data VkQueryPool_T Source #

Opaque data type referenced by VkQueryPool

data VkQueue_T Source #

Opaque data type referenced by VkQueue

data VkRenderPass_T Source #

Opaque data type referenced by VkRenderPass

data VkSampler_T Source #

Opaque data type referenced by VkSampler

data VkSamplerYcbcrConversion_T Source #

Opaque data type referenced by VkSamplerYcbcrConversion

data VkSamplerYcbcrConversionKHR_T Source #

Opaque data type referenced by VkSamplerYcbcrConversionKHR

data VkSemaphore_T Source #

Opaque data type referenced by VkSemaphore

data VkShaderModule_T Source #

Opaque data type referenced by VkShaderModule

data VkSurfaceKHR_T Source #

Opaque data type referenced by VkSurfaceKHR

data VkSwapchainKHR_T Source #

Opaque data type referenced by VkSwapchainKHR

data VkValidationCacheEXT_T Source #

Opaque data type referenced by VkValidationCacheEXT

type DWORD = Word32 Source #

Requires windows.h

data Display Source #

Requires X11/Xlib.h

data GgpFrameToken Source #

Requires ggp_c/vulkan_types.h

data GgpStreamDescriptor Source #

Requires ggp_c/vulkan_types.h

type HANDLE = Ptr () Source #

Requires windows.h

type HINSTANCE = Ptr () Source #

Requires windows.h

data HMONITOR Source #

Requires windows.h

type HWND = Ptr () Source #

Requires windows.h

data IDirectFB Source #

Requires directfb.h

data IDirectFBSurface Source #

Requires directfb.h

type LPCWSTR = Ptr CWchar Source #

Requires windows.h

type RROutput = CULong Source #

Requires X11extensionsXrandr.h

data SECURITY_ATTRIBUTES Source #

Requires windows.h

type VisualID = CULong Source #

Requires X11/Xlib.h

type Window = CULong Source #

Requires X11/Xlib.h

data WlDisplay Source #

Requires wayland-client.h

data WlSurface Source #

Requires wayland-client.h

data XcbConnectionT Source #

Requires xcb/xcb.h

type XcbVisualidT = CULong Source #

Requires xcb/xcb.h

type XcbWindowT = CULong Source #

Requires xcb/xcb.h

data Zx_handle_t Source #

Requires zircon/types.h