vulkan-3.1.0.0: Bindings to the Vulkan graphics API.

Safe HaskellNone
LanguageHaskell2010

Graphics.Vulkan.Extensions.VK_KHR_xlib_surface

Synopsis

Documentation

createXlibSurfaceKHR :: forall io. MonadIO io => Instance -> XlibSurfaceCreateInfoKHR -> ("allocator" ::: Maybe AllocationCallbacks) -> io SurfaceKHR Source #

vkCreateXlibSurfaceKHR - Create a SurfaceKHR object for an X11 window, using the Xlib client-side library

Parameters

  • instance is the instance to associate the surface with.
  • pCreateInfo is a pointer to a XlibSurfaceCreateInfoKHR structure containing the 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 is a pointer to a SurfaceKHR handle in which the created surface object is returned.

Valid Usage (Implicit)

  • instance must be a valid Instance handle

Return Codes

Success
Failure

See Also

AllocationCallbacks, Instance, SurfaceKHR, XlibSurfaceCreateInfoKHR

getPhysicalDeviceXlibPresentationSupportKHR :: forall io. MonadIO io => PhysicalDevice -> ("queueFamilyIndex" ::: Word32) -> ("dpy" ::: Ptr Display) -> VisualID -> io Bool Source #

vkGetPhysicalDeviceXlibPresentationSupportKHR - Query physical device for presentation to X11 server using Xlib

Parameters

  • physicalDevice is the physical device.
  • queueFamilyIndex is the queue family index.
  • dpy is a pointer to an Xlib Display connection to the server.
  • visualId is an X11 visual (VisualID).

Description

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

Valid Usage (Implicit)

See Also

PhysicalDevice

data XlibSurfaceCreateInfoKHR Source #

VkXlibSurfaceCreateInfoKHR - Structure specifying parameters of a newly created Xlib surface object

Valid Usage (Implicit)

See Also

StructureType, XlibSurfaceCreateFlagsKHR, createXlibSurfaceKHR

Constructors

XlibSurfaceCreateInfoKHR 

Fields

Instances
Show XlibSurfaceCreateInfoKHR Source # 
Instance details

Defined in Graphics.Vulkan.Extensions.VK_KHR_xlib_surface

Storable XlibSurfaceCreateInfoKHR Source # 
Instance details

Defined in Graphics.Vulkan.Extensions.VK_KHR_xlib_surface

FromCStruct XlibSurfaceCreateInfoKHR Source # 
Instance details

Defined in Graphics.Vulkan.Extensions.VK_KHR_xlib_surface

ToCStruct XlibSurfaceCreateInfoKHR Source # 
Instance details

Defined in Graphics.Vulkan.Extensions.VK_KHR_xlib_surface

Zero XlibSurfaceCreateInfoKHR Source # 
Instance details

Defined in Graphics.Vulkan.Extensions.VK_KHR_xlib_surface

newtype XlibSurfaceCreateFlagsKHR Source #

Instances
Eq XlibSurfaceCreateFlagsKHR Source # 
Instance details

Defined in Graphics.Vulkan.Extensions.VK_KHR_xlib_surface

Ord XlibSurfaceCreateFlagsKHR Source # 
Instance details

Defined in Graphics.Vulkan.Extensions.VK_KHR_xlib_surface

Read XlibSurfaceCreateFlagsKHR Source # 
Instance details

Defined in Graphics.Vulkan.Extensions.VK_KHR_xlib_surface

Show XlibSurfaceCreateFlagsKHR Source # 
Instance details

Defined in Graphics.Vulkan.Extensions.VK_KHR_xlib_surface

Storable XlibSurfaceCreateFlagsKHR Source # 
Instance details

Defined in Graphics.Vulkan.Extensions.VK_KHR_xlib_surface

Bits XlibSurfaceCreateFlagsKHR Source # 
Instance details

Defined in Graphics.Vulkan.Extensions.VK_KHR_xlib_surface

Methods

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

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

xor :: XlibSurfaceCreateFlagsKHR -> XlibSurfaceCreateFlagsKHR -> XlibSurfaceCreateFlagsKHR #

complement :: XlibSurfaceCreateFlagsKHR -> XlibSurfaceCreateFlagsKHR #

shift :: XlibSurfaceCreateFlagsKHR -> Int -> XlibSurfaceCreateFlagsKHR #

rotate :: XlibSurfaceCreateFlagsKHR -> Int -> XlibSurfaceCreateFlagsKHR #

zeroBits :: XlibSurfaceCreateFlagsKHR #

bit :: Int -> XlibSurfaceCreateFlagsKHR #

setBit :: XlibSurfaceCreateFlagsKHR -> Int -> XlibSurfaceCreateFlagsKHR #

clearBit :: XlibSurfaceCreateFlagsKHR -> Int -> XlibSurfaceCreateFlagsKHR #

complementBit :: XlibSurfaceCreateFlagsKHR -> Int -> XlibSurfaceCreateFlagsKHR #

testBit :: XlibSurfaceCreateFlagsKHR -> Int -> Bool #

bitSizeMaybe :: XlibSurfaceCreateFlagsKHR -> Maybe Int #

bitSize :: XlibSurfaceCreateFlagsKHR -> Int #

isSigned :: XlibSurfaceCreateFlagsKHR -> Bool #

shiftL :: XlibSurfaceCreateFlagsKHR -> Int -> XlibSurfaceCreateFlagsKHR #

unsafeShiftL :: XlibSurfaceCreateFlagsKHR -> Int -> XlibSurfaceCreateFlagsKHR #

shiftR :: XlibSurfaceCreateFlagsKHR -> Int -> XlibSurfaceCreateFlagsKHR #

unsafeShiftR :: XlibSurfaceCreateFlagsKHR -> Int -> XlibSurfaceCreateFlagsKHR #

rotateL :: XlibSurfaceCreateFlagsKHR -> Int -> XlibSurfaceCreateFlagsKHR #

rotateR :: XlibSurfaceCreateFlagsKHR -> Int -> XlibSurfaceCreateFlagsKHR #

popCount :: XlibSurfaceCreateFlagsKHR -> Int #

Zero XlibSurfaceCreateFlagsKHR Source # 
Instance details

Defined in Graphics.Vulkan.Extensions.VK_KHR_xlib_surface

pattern KHR_XLIB_SURFACE_SPEC_VERSION :: forall a. Integral a => a Source #

type KHR_XLIB_SURFACE_EXTENSION_NAME = "VK_KHR_xlib_surface" Source #

pattern KHR_XLIB_SURFACE_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a Source #

newtype SurfaceKHR Source #

Constructors

SurfaceKHR Word64 

type Display = Ptr () Source #