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

Vulkan.Extensions.VK_EXT_directfb_surface

Synopsis

Documentation

createDirectFBSurfaceEXT Source #

Arguments

:: forall io. MonadIO io 
=> Instance

instance is the instance to associate the surface with.

-> DirectFBSurfaceCreateInfoEXT

pCreateInfo is a pointer to a DirectFBSurfaceCreateInfoEXT structure containing 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 

vkCreateDirectFBSurfaceEXT - Create a SurfaceKHR object for a DirectFB surface

Valid Usage (Implicit)

  • instance must be a valid Instance handle

Return Codes

Success
Failure

See Also

AllocationCallbacks, DirectFBSurfaceCreateInfoEXT, Instance, SurfaceKHR

getPhysicalDeviceDirectFBPresentationSupportEXT 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

-> ("dfb" ::: Ptr IDirectFB)

dfb is a pointer to the IDirectFB main interface of DirectFB.

dfb must be a valid pointer to an IDirectFB value

-> io Bool 

vkGetPhysicalDeviceDirectFBPresentationSupportEXT - Query physical device for presentation with DirectFB

Description

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

Valid Usage (Implicit)

See Also

PhysicalDevice

data DirectFBSurfaceCreateInfoEXT Source #

VkDirectFBSurfaceCreateInfoEXT - Structure specifying parameters of a newly created DirectFB surface object

Valid Usage (Implicit)

See Also

DirectFBSurfaceCreateFlagsEXT, StructureType, createDirectFBSurfaceEXT

Constructors

DirectFBSurfaceCreateInfoEXT 

Fields

Instances

Instances details
Eq DirectFBSurfaceCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_directfb_surface

Show DirectFBSurfaceCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_directfb_surface

Generic DirectFBSurfaceCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_directfb_surface

Associated Types

type Rep DirectFBSurfaceCreateInfoEXT :: Type -> Type #

Storable DirectFBSurfaceCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_directfb_surface

FromCStruct DirectFBSurfaceCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_directfb_surface

ToCStruct DirectFBSurfaceCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_directfb_surface

Zero DirectFBSurfaceCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_directfb_surface

type Rep DirectFBSurfaceCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_directfb_surface

type Rep DirectFBSurfaceCreateInfoEXT = D1 ('MetaData "DirectFBSurfaceCreateInfoEXT" "Vulkan.Extensions.VK_EXT_directfb_surface" "vulkan-3.6-inplace" 'False) (C1 ('MetaCons "DirectFBSurfaceCreateInfoEXT" 'PrefixI 'True) (S1 ('MetaSel ('Just "flags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 DirectFBSurfaceCreateFlagsEXT) :*: (S1 ('MetaSel ('Just "dfb") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Ptr IDirectFB)) :*: S1 ('MetaSel ('Just "surface") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Ptr IDirectFBSurface)))))

newtype DirectFBSurfaceCreateFlagsEXT Source #

VkDirectFBSurfaceCreateFlagsEXT - Reserved for future use

Description

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

See Also

DirectFBSurfaceCreateInfoEXT

Instances

Instances details
Eq DirectFBSurfaceCreateFlagsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_directfb_surface

Ord DirectFBSurfaceCreateFlagsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_directfb_surface

Read DirectFBSurfaceCreateFlagsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_directfb_surface

Show DirectFBSurfaceCreateFlagsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_directfb_surface

Storable DirectFBSurfaceCreateFlagsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_directfb_surface

Bits DirectFBSurfaceCreateFlagsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_directfb_surface

Methods

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

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

xor :: DirectFBSurfaceCreateFlagsEXT -> DirectFBSurfaceCreateFlagsEXT -> DirectFBSurfaceCreateFlagsEXT #

complement :: DirectFBSurfaceCreateFlagsEXT -> DirectFBSurfaceCreateFlagsEXT #

shift :: DirectFBSurfaceCreateFlagsEXT -> Int -> DirectFBSurfaceCreateFlagsEXT #

rotate :: DirectFBSurfaceCreateFlagsEXT -> Int -> DirectFBSurfaceCreateFlagsEXT #

zeroBits :: DirectFBSurfaceCreateFlagsEXT #

bit :: Int -> DirectFBSurfaceCreateFlagsEXT #

setBit :: DirectFBSurfaceCreateFlagsEXT -> Int -> DirectFBSurfaceCreateFlagsEXT #

clearBit :: DirectFBSurfaceCreateFlagsEXT -> Int -> DirectFBSurfaceCreateFlagsEXT #

complementBit :: DirectFBSurfaceCreateFlagsEXT -> Int -> DirectFBSurfaceCreateFlagsEXT #

testBit :: DirectFBSurfaceCreateFlagsEXT -> Int -> Bool #

bitSizeMaybe :: DirectFBSurfaceCreateFlagsEXT -> Maybe Int #

bitSize :: DirectFBSurfaceCreateFlagsEXT -> Int #

isSigned :: DirectFBSurfaceCreateFlagsEXT -> Bool #

shiftL :: DirectFBSurfaceCreateFlagsEXT -> Int -> DirectFBSurfaceCreateFlagsEXT #

unsafeShiftL :: DirectFBSurfaceCreateFlagsEXT -> Int -> DirectFBSurfaceCreateFlagsEXT #

shiftR :: DirectFBSurfaceCreateFlagsEXT -> Int -> DirectFBSurfaceCreateFlagsEXT #

unsafeShiftR :: DirectFBSurfaceCreateFlagsEXT -> Int -> DirectFBSurfaceCreateFlagsEXT #

rotateL :: DirectFBSurfaceCreateFlagsEXT -> Int -> DirectFBSurfaceCreateFlagsEXT #

rotateR :: DirectFBSurfaceCreateFlagsEXT -> Int -> DirectFBSurfaceCreateFlagsEXT #

popCount :: DirectFBSurfaceCreateFlagsEXT -> Int #

Zero DirectFBSurfaceCreateFlagsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_directfb_surface

type EXT_DIRECTFB_SURFACE_EXTENSION_NAME = "VK_EXT_directfb_surface" Source #

pattern EXT_DIRECTFB_SURFACE_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a 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