vulkan-2.0.0.1: Bindings to the Vulkan graphics API.

Safe HaskellNone
LanguageHaskell2010

Graphics.Vulkan.Extensions.VK_KHR_xcb_surface

Synopsis

Documentation

data Xcb_connection_t Source #

Opaque data

newtype VkXcbSurfaceCreateFlagsKHR Source #

Instances
Eq VkXcbSurfaceCreateFlagsKHR Source # 
Instance details
Ord VkXcbSurfaceCreateFlagsKHR Source # 
Instance details
Read VkXcbSurfaceCreateFlagsKHR Source # 
Instance details
Show VkXcbSurfaceCreateFlagsKHR Source # 
Instance details
Storable VkXcbSurfaceCreateFlagsKHR Source # 
Instance details
Bits VkXcbSurfaceCreateFlagsKHR Source # 
Instance details

Methods

(.&.) :: VkXcbSurfaceCreateFlagsKHR -> VkXcbSurfaceCreateFlagsKHR -> VkXcbSurfaceCreateFlagsKHR #

(.|.) :: VkXcbSurfaceCreateFlagsKHR -> VkXcbSurfaceCreateFlagsKHR -> VkXcbSurfaceCreateFlagsKHR #

xor :: VkXcbSurfaceCreateFlagsKHR -> VkXcbSurfaceCreateFlagsKHR -> VkXcbSurfaceCreateFlagsKHR #

complement :: VkXcbSurfaceCreateFlagsKHR -> VkXcbSurfaceCreateFlagsKHR #

shift :: VkXcbSurfaceCreateFlagsKHR -> Int -> VkXcbSurfaceCreateFlagsKHR #

rotate :: VkXcbSurfaceCreateFlagsKHR -> Int -> VkXcbSurfaceCreateFlagsKHR #

zeroBits :: VkXcbSurfaceCreateFlagsKHR #

bit :: Int -> VkXcbSurfaceCreateFlagsKHR #

setBit :: VkXcbSurfaceCreateFlagsKHR -> Int -> VkXcbSurfaceCreateFlagsKHR #

clearBit :: VkXcbSurfaceCreateFlagsKHR -> Int -> VkXcbSurfaceCreateFlagsKHR #

complementBit :: VkXcbSurfaceCreateFlagsKHR -> Int -> VkXcbSurfaceCreateFlagsKHR #

testBit :: VkXcbSurfaceCreateFlagsKHR -> Int -> Bool #

bitSizeMaybe :: VkXcbSurfaceCreateFlagsKHR -> Maybe Int #

bitSize :: VkXcbSurfaceCreateFlagsKHR -> Int #

isSigned :: VkXcbSurfaceCreateFlagsKHR -> Bool #

shiftL :: VkXcbSurfaceCreateFlagsKHR -> Int -> VkXcbSurfaceCreateFlagsKHR #

unsafeShiftL :: VkXcbSurfaceCreateFlagsKHR -> Int -> VkXcbSurfaceCreateFlagsKHR #

shiftR :: VkXcbSurfaceCreateFlagsKHR -> Int -> VkXcbSurfaceCreateFlagsKHR #

unsafeShiftR :: VkXcbSurfaceCreateFlagsKHR -> Int -> VkXcbSurfaceCreateFlagsKHR #

rotateL :: VkXcbSurfaceCreateFlagsKHR -> Int -> VkXcbSurfaceCreateFlagsKHR #

rotateR :: VkXcbSurfaceCreateFlagsKHR -> Int -> VkXcbSurfaceCreateFlagsKHR #

popCount :: VkXcbSurfaceCreateFlagsKHR -> Int #

FiniteBits VkXcbSurfaceCreateFlagsKHR Source # 
Instance details

vkCreateXcbSurfaceKHR :: ("instance" ::: VkInstance) -> ("pCreateInfo" ::: Ptr VkXcbSurfaceCreateInfoKHR) -> ("pAllocator" ::: Ptr VkAllocationCallbacks) -> ("pSurface" ::: Ptr VkSurfaceKHR) -> IO VkResult Source #

vkCreateXcbSurfaceKHR - Create a VkSurfaceKHR object for a X11 window, using the XCB client-side library

Parameters

  • instance is the instance to associate the surface with.
  • pCreateInfo is a pointer to an instance of the VkXcbSurfaceCreateInfoKHR structure containing parameters affecting the creation of the surface object.
  • pAllocator is the allocator used for host memory allocated for the surface object when there is no more specific allocator available (see Memory Allocation).
  • pSurface points to a VkSurfaceKHR handle in which the created surface object is returned.

Valid Usage (Implicit)

  • instance must be a valid VkInstance handle
  • pCreateInfo must be a valid pointer to a valid VkXcbSurfaceCreateInfoKHR structure
  • If pAllocator is not NULL, pAllocator must be a valid pointer to a valid VkAllocationCallbacks structure
  • pSurface must be a valid pointer to a VkSurfaceKHR handle

Return Codes

[Success] - VK_SUCCESS

[Failure] - VK_ERROR_OUT_OF_HOST_MEMORY

  • VK_ERROR_OUT_OF_DEVICE_MEMORY

See Also

VkAllocationCallbacks, VkInstance, VkSurfaceKHR, VkXcbSurfaceCreateInfoKHR

vkGetPhysicalDeviceXcbPresentationSupportKHR :: ("physicalDevice" ::: VkPhysicalDevice) -> ("queueFamilyIndex" ::: Word32) -> ("connection" ::: Ptr Xcb_connection_t) -> ("visual_id" ::: Xcb_visualid_t) -> IO VkBool32 Source #

vkGetPhysicalDeviceXcbPresentationSupportKHR - Query physical device for presentation to X11 server using XCB

Parameters

  • physicalDevice is the physical device.
  • queueFamilyIndex is the queue family index.
  • connection is a pointer to an xcb_connection_t to the X server. visual_id is an X11 visual (xcb_visualid_t).

Description

This platform-specific function can be called prior to creating a surface.

Valid Usage

  • queueFamilyIndex must be less than pQueueFamilyPropertyCount returned by vkGetPhysicalDeviceQueueFamilyProperties for the given physicalDevice

Valid Usage (Implicit)

  • physicalDevice must be a valid VkPhysicalDevice handle
  • connection must be a valid pointer to a xcb_connection_t value

See Also

VkPhysicalDevice

data VkXcbSurfaceCreateInfoKHR Source #

VkXcbSurfaceCreateInfoKHR - Structure specifying parameters of a newly created Xcb surface object

Valid Usage

  • connection must point to a valid X11 xcb_connection_t.
  • window must be a valid X11 xcb_window_t.

Valid Usage (Implicit)

  • sType must be VK_STRUCTURE_TYPE_XCB_SURFACE_CREATE_INFO_KHR
  • pNext must be NULL
  • flags must be 0

See Also

VkStructureType, VkXcbSurfaceCreateFlagsKHR, vkCreateXcbSurfaceKHR

Constructors

VkXcbSurfaceCreateInfoKHR 

Fields