vulkan-3.6.4: Bindings to the Vulkan graphics API.
Safe HaskellNone
LanguageHaskell2010

Vulkan.Extensions.VK_KHR_xlib_surface

Synopsis

Documentation

createXlibSurfaceKHR Source #

Arguments

:: forall io. MonadIO io 
=> Instance

instance is the instance to associate the surface with.

-> XlibSurfaceCreateInfoKHR

pCreateInfo is a pointer to a XlibSurfaceCreateInfoKHR structure containing the parameters affecting the creation of the surface object.

-> ("allocator" ::: Maybe AllocationCallbacks)

pAllocator is the allocator used for host memory allocated for the surface object when there is no more specific allocator available (see Memory Allocation).

-> io SurfaceKHR 

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

Valid Usage (Implicit)

  • instance must be a valid Instance handle

Return Codes

Success
Failure

See Also

AllocationCallbacks, Instance, SurfaceKHR, XlibSurfaceCreateInfoKHR

getPhysicalDeviceXlibPresentationSupportKHR Source #

Arguments

:: forall io. MonadIO io 
=> PhysicalDevice

physicalDevice is the physical device.

physicalDevice must be a valid PhysicalDevice handle

-> ("queueFamilyIndex" ::: Word32)

queueFamilyIndex is the queue family index.

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

-> ("dpy" ::: Ptr Display)

dpy is a pointer to an Xlib Display connection to the server.

dpy must be a valid pointer to a Display value

-> VisualID 
-> io Bool 

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

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

Instances details
Eq XlibSurfaceCreateInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_xlib_surface

Show XlibSurfaceCreateInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_xlib_surface

Generic XlibSurfaceCreateInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_xlib_surface

Associated Types

type Rep XlibSurfaceCreateInfoKHR :: Type -> Type #

Storable XlibSurfaceCreateInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_xlib_surface

FromCStruct XlibSurfaceCreateInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_xlib_surface

ToCStruct XlibSurfaceCreateInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_xlib_surface

Zero XlibSurfaceCreateInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_xlib_surface

type Rep XlibSurfaceCreateInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_xlib_surface

type Rep XlibSurfaceCreateInfoKHR = D1 ('MetaData "XlibSurfaceCreateInfoKHR" "Vulkan.Extensions.VK_KHR_xlib_surface" "vulkan-3.6.4-inplace" 'False) (C1 ('MetaCons "XlibSurfaceCreateInfoKHR" 'PrefixI 'True) (S1 ('MetaSel ('Just "flags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 XlibSurfaceCreateFlagsKHR) :*: (S1 ('MetaSel ('Just "dpy") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Ptr Display)) :*: S1 ('MetaSel ('Just "window") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Window))))

newtype XlibSurfaceCreateFlagsKHR Source #

VkXlibSurfaceCreateFlagsKHR - Reserved for future use

Description

XlibSurfaceCreateFlagsKHR is a bitmask type for setting a mask, but is currently reserved for future use.

See Also

XlibSurfaceCreateInfoKHR

Instances

Instances details
Eq XlibSurfaceCreateFlagsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_xlib_surface

Ord XlibSurfaceCreateFlagsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_xlib_surface

Read XlibSurfaceCreateFlagsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_xlib_surface

Show XlibSurfaceCreateFlagsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_xlib_surface

Storable XlibSurfaceCreateFlagsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_xlib_surface

Bits XlibSurfaceCreateFlagsKHR Source # 
Instance details

Defined in 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 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 #

type Display = Ptr () Source #

newtype SurfaceKHR Source #

Constructors

SurfaceKHR Word64 

Instances

Instances details
Eq SurfaceKHR Source # 
Instance details

Defined in Vulkan.Extensions.Handles

Ord SurfaceKHR Source # 
Instance details

Defined in Vulkan.Extensions.Handles

Show SurfaceKHR Source # 
Instance details

Defined in Vulkan.Extensions.Handles

Storable SurfaceKHR Source # 
Instance details

Defined in Vulkan.Extensions.Handles

Zero SurfaceKHR Source # 
Instance details

Defined in Vulkan.Extensions.Handles

HasObjectType SurfaceKHR Source # 
Instance details

Defined in Vulkan.Extensions.Handles

IsHandle SurfaceKHR Source # 
Instance details

Defined in Vulkan.Extensions.Handles