{-# language CPP #-}
-- | = Name
--
-- VK_KHR_xcb_surface - instance extension
--
-- == VK_KHR_xcb_surface
--
-- [__Name String__]
--     @VK_KHR_xcb_surface@
--
-- [__Extension Type__]
--     Instance extension
--
-- [__Registered Extension Number__]
--     6
--
-- [__Revision__]
--     6
--
-- [__Extension and Version Dependencies__]
--
--     -   Requires Vulkan 1.0
--
--     -   Requires @VK_KHR_surface@
--
-- [__Contact__]
--
--     -   Jesse Hall
--         <https://github.com/KhronosGroup/Vulkan-Docs/issues/new?body=[VK_KHR_xcb_surface] @critsec%0A<<Here describe the issue or question you have about the VK_KHR_xcb_surface extension>> >
--
--     -   Ian Elliott
--         <https://github.com/KhronosGroup/Vulkan-Docs/issues/new?body=[VK_KHR_xcb_surface] @ianelliottus%0A<<Here describe the issue or question you have about the VK_KHR_xcb_surface extension>> >
--
-- == Other Extension Metadata
--
-- [__Last Modified Date__]
--     2015-11-28
--
-- [__IP Status__]
--     No known IP claims.
--
-- [__Contributors__]
--
--     -   Patrick Doane, Blizzard
--
--     -   Jason Ekstrand, Intel
--
--     -   Ian Elliott, LunarG
--
--     -   Courtney Goeltzenleuchter, LunarG
--
--     -   Jesse Hall, Google
--
--     -   James Jones, NVIDIA
--
--     -   Antoine Labour, Google
--
--     -   Jon Leech, Khronos
--
--     -   David Mao, AMD
--
--     -   Norbert Nopper, Freescale
--
--     -   Alon Or-bach, Samsung
--
--     -   Daniel Rakos, AMD
--
--     -   Graham Sellers, AMD
--
--     -   Ray Smith, ARM
--
--     -   Jeff Vigil, Qualcomm
--
--     -   Chia-I Wu, LunarG
--
-- == Description
--
-- The @VK_KHR_xcb_surface@ extension is an instance extension. It provides
-- a mechanism to create a 'Vulkan.Extensions.Handles.SurfaceKHR' object
-- (defined by the @VK_KHR_surface@ extension) that refers to an X11
-- 'Vulkan.Extensions.VK_KHR_xlib_surface.Window', using the XCB
-- client-side library, as well as a query to determine support for
-- rendering via XCB.
--
-- == New Commands
--
-- -   'createXcbSurfaceKHR'
--
-- -   'getPhysicalDeviceXcbPresentationSupportKHR'
--
-- == New Structures
--
-- -   'XcbSurfaceCreateInfoKHR'
--
-- == New Bitmasks
--
-- -   'XcbSurfaceCreateFlagsKHR'
--
-- == New Enum Constants
--
-- -   'KHR_XCB_SURFACE_EXTENSION_NAME'
--
-- -   'KHR_XCB_SURFACE_SPEC_VERSION'
--
-- -   Extending 'Vulkan.Core10.Enums.StructureType.StructureType':
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_XCB_SURFACE_CREATE_INFO_KHR'
--
-- == Issues
--
-- 1) Does XCB need a way to query for compatibility between a particular
-- physical device and a specific screen? This would be a more general
-- query than
-- 'Vulkan.Extensions.VK_KHR_surface.getPhysicalDeviceSurfaceSupportKHR':
-- If it returned 'Vulkan.Core10.FundamentalTypes.TRUE', then the physical
-- device could be assumed to support presentation to any window on that
-- screen.
--
-- __RESOLVED__: Yes, this is needed for toolkits that want to create a
-- 'Vulkan.Core10.Handles.Device' before creating a window. To ensure the
-- query is reliable, it must be made against a particular X visual rather
-- than the screen in general.
--
-- == Version History
--
-- -   Revision 1, 2015-09-23 (Jesse Hall)
--
--     -   Initial draft, based on the previous contents of
--         VK_EXT_KHR_swapchain (later renamed VK_EXT_KHR_surface).
--
-- -   Revision 2, 2015-10-02 (James Jones)
--
--     -   Added presentation support query for an (xcb_connection_t*,
--         xcb_visualid_t) pair.
--
--     -   Removed “root” parameter from CreateXcbSurfaceKHR(), as it is
--         redundant when a window on the same screen is specified as well.
--
--     -   Adjusted wording of issue #1 and added agreed upon resolution.
--
-- -   Revision 3, 2015-10-14 (Ian Elliott)
--
--     -   Removed “root” parameter from CreateXcbSurfaceKHR() in one more
--         place.
--
-- -   Revision 4, 2015-10-26 (Ian Elliott)
--
--     -   Renamed from VK_EXT_KHR_xcb_surface to VK_KHR_xcb_surface.
--
-- -   Revision 5, 2015-10-23 (Daniel Rakos)
--
--     -   Added allocation callbacks to vkCreateXcbSurfaceKHR.
--
-- -   Revision 6, 2015-11-28 (Daniel Rakos)
--
--     -   Updated the surface create function to take a pCreateInfo
--         structure.
--
-- = See Also
--
-- 'XcbSurfaceCreateFlagsKHR', 'XcbSurfaceCreateInfoKHR',
-- 'createXcbSurfaceKHR', 'getPhysicalDeviceXcbPresentationSupportKHR'
--
-- = Document Notes
--
-- For more information, see the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_KHR_xcb_surface Vulkan Specification>
--
-- This page is a generated document. Fixes and changes should be made to
-- the generator scripts, not directly.
module Vulkan.Extensions.VK_KHR_xcb_surface  ( createXcbSurfaceKHR
                                             , getPhysicalDeviceXcbPresentationSupportKHR
                                             , XcbSurfaceCreateInfoKHR(..)
                                             , XcbSurfaceCreateFlagsKHR(..)
                                             , KHR_XCB_SURFACE_SPEC_VERSION
                                             , pattern KHR_XCB_SURFACE_SPEC_VERSION
                                             , KHR_XCB_SURFACE_EXTENSION_NAME
                                             , pattern KHR_XCB_SURFACE_EXTENSION_NAME
                                             , Xcb_visualid_t
                                             , Xcb_window_t
                                             , Xcb_connection_t
                                             , SurfaceKHR(..)
                                             ) where

import Vulkan.Internal.Utils (enumReadPrec)
import Vulkan.Internal.Utils (enumShowsPrec)
import Vulkan.Internal.Utils (traceAroundEvent)
import Control.Exception.Base (bracket)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Foreign.Marshal.Alloc (allocaBytes)
import Foreign.Marshal.Alloc (callocBytes)
import Foreign.Marshal.Alloc (free)
import GHC.Base (when)
import GHC.IO (throwIO)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import GHC.Show (showString)
import Numeric (showHex)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero)
import Vulkan.Zero (Zero(..))
import Control.Monad.IO.Class (MonadIO)
import Data.Bits (Bits)
import Data.Bits (FiniteBits)
import Data.String (IsString)
import Data.Typeable (Typeable)
import Foreign.Storable (Storable)
import Foreign.Storable (Storable(peek))
import Foreign.Storable (Storable(poke))
import qualified Foreign.Storable (Storable(..))
import GHC.Generics (Generic)
import GHC.IO.Exception (IOErrorType(..))
import GHC.IO.Exception (IOException(..))
import Foreign.Ptr (FunPtr)
import Foreign.Ptr (Ptr)
import GHC.Read (Read(readPrec))
import GHC.Show (Show(showsPrec))
import Data.Word (Word32)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.NamedType ((:::))
import Vulkan.Core10.AllocationCallbacks (AllocationCallbacks)
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.Core10.FundamentalTypes (Bool32(..))
import Vulkan.Core10.FundamentalTypes (Flags)
import Vulkan.Core10.Handles (Instance)
import Vulkan.Core10.Handles (Instance(..))
import Vulkan.Dynamic (InstanceCmds(pVkCreateXcbSurfaceKHR))
import Vulkan.Dynamic (InstanceCmds(pVkGetPhysicalDeviceXcbPresentationSupportKHR))
import Vulkan.Core10.Handles (Instance_T)
import Vulkan.Core10.Handles (PhysicalDevice)
import Vulkan.Core10.Handles (PhysicalDevice(..))
import Vulkan.Core10.Handles (PhysicalDevice_T)
import Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Extensions.Handles (SurfaceKHR)
import Vulkan.Extensions.Handles (SurfaceKHR(..))
import Vulkan.Exception (VulkanException(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_XCB_SURFACE_CREATE_INFO_KHR))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
import Vulkan.Extensions.Handles (SurfaceKHR(..))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCreateXcbSurfaceKHR
  :: FunPtr (Ptr Instance_T -> Ptr XcbSurfaceCreateInfoKHR -> Ptr AllocationCallbacks -> Ptr SurfaceKHR -> IO Result) -> Ptr Instance_T -> Ptr XcbSurfaceCreateInfoKHR -> Ptr AllocationCallbacks -> Ptr SurfaceKHR -> IO Result

-- | vkCreateXcbSurfaceKHR - Create a 'Vulkan.Extensions.Handles.SurfaceKHR'
-- object for a X11 window, using the XCB client-side library
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCreateXcbSurfaceKHR-instance-parameter# @instance@ /must/ be
--     a valid 'Vulkan.Core10.Handles.Instance' handle
--
-- -   #VUID-vkCreateXcbSurfaceKHR-pCreateInfo-parameter# @pCreateInfo@
--     /must/ be a valid pointer to a valid 'XcbSurfaceCreateInfoKHR'
--     structure
--
-- -   #VUID-vkCreateXcbSurfaceKHR-pAllocator-parameter# If @pAllocator@ is
--     not @NULL@, @pAllocator@ /must/ be a valid pointer to a valid
--     'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' structure
--
-- -   #VUID-vkCreateXcbSurfaceKHR-pSurface-parameter# @pSurface@ /must/ be
--     a valid pointer to a 'Vulkan.Extensions.Handles.SurfaceKHR' handle
--
-- == Return Codes
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>]
--
--     -   'Vulkan.Core10.Enums.Result.SUCCESS'
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-errorcodes Failure>]
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_DEVICE_MEMORY'
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_KHR_xcb_surface VK_KHR_xcb_surface>,
-- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks',
-- 'Vulkan.Core10.Handles.Instance',
-- 'Vulkan.Extensions.Handles.SurfaceKHR', 'XcbSurfaceCreateInfoKHR'
createXcbSurfaceKHR :: forall io
                     . (MonadIO io)
                    => -- | @instance@ is the instance to associate the surface with.
                       Instance
                    -> -- | @pCreateInfo@ is a pointer to a 'XcbSurfaceCreateInfoKHR' structure
                       -- containing parameters affecting the creation of the surface object.
                       XcbSurfaceCreateInfoKHR
                    -> -- | @pAllocator@ is the allocator used for host memory allocated for the
                       -- surface object when there is no more specific allocator available (see
                       -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#memory-allocation Memory Allocation>).
                       ("allocator" ::: Maybe AllocationCallbacks)
                    -> io (SurfaceKHR)
createXcbSurfaceKHR :: Instance
-> XcbSurfaceCreateInfoKHR
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io SurfaceKHR
createXcbSurfaceKHR Instance
instance' XcbSurfaceCreateInfoKHR
createInfo "allocator" ::: Maybe AllocationCallbacks
allocator = IO SurfaceKHR -> io SurfaceKHR
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SurfaceKHR -> io SurfaceKHR)
-> (ContT SurfaceKHR IO SurfaceKHR -> IO SurfaceKHR)
-> ContT SurfaceKHR IO SurfaceKHR
-> io SurfaceKHR
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT SurfaceKHR IO SurfaceKHR -> IO SurfaceKHR
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT SurfaceKHR IO SurfaceKHR -> io SurfaceKHR)
-> ContT SurfaceKHR IO SurfaceKHR -> io SurfaceKHR
forall a b. (a -> b) -> a -> b
$ do
  let vkCreateXcbSurfaceKHRPtr :: FunPtr
  (Ptr Instance_T
   -> ("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pSurface" ::: Ptr SurfaceKHR)
   -> IO Result)
vkCreateXcbSurfaceKHRPtr = InstanceCmds
-> FunPtr
     (Ptr Instance_T
      -> ("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR)
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> ("pSurface" ::: Ptr SurfaceKHR)
      -> IO Result)
pVkCreateXcbSurfaceKHR (Instance -> InstanceCmds
instanceCmds (Instance
instance' :: Instance))
  IO () -> ContT SurfaceKHR IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT SurfaceKHR IO ())
-> IO () -> ContT SurfaceKHR IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Instance_T
   -> ("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pSurface" ::: Ptr SurfaceKHR)
   -> IO Result)
vkCreateXcbSurfaceKHRPtr FunPtr
  (Ptr Instance_T
   -> ("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pSurface" ::: Ptr SurfaceKHR)
   -> IO Result)
-> FunPtr
     (Ptr Instance_T
      -> ("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR)
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> ("pSurface" ::: Ptr SurfaceKHR)
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Instance_T
   -> ("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pSurface" ::: Ptr SurfaceKHR)
   -> IO Result)
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkCreateXcbSurfaceKHR is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCreateXcbSurfaceKHR' :: Ptr Instance_T
-> ("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pSurface" ::: Ptr SurfaceKHR)
-> IO Result
vkCreateXcbSurfaceKHR' = FunPtr
  (Ptr Instance_T
   -> ("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pSurface" ::: Ptr SurfaceKHR)
   -> IO Result)
-> Ptr Instance_T
-> ("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pSurface" ::: Ptr SurfaceKHR)
-> IO Result
mkVkCreateXcbSurfaceKHR FunPtr
  (Ptr Instance_T
   -> ("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pSurface" ::: Ptr SurfaceKHR)
   -> IO Result)
vkCreateXcbSurfaceKHRPtr
  "pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR
pCreateInfo <- ((("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR) -> IO SurfaceKHR)
 -> IO SurfaceKHR)
-> ContT
     SurfaceKHR IO ("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR)
   -> IO SurfaceKHR)
  -> IO SurfaceKHR)
 -> ContT
      SurfaceKHR IO ("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR))
-> ((("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR)
     -> IO SurfaceKHR)
    -> IO SurfaceKHR)
-> ContT
     SurfaceKHR IO ("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR)
forall a b. (a -> b) -> a -> b
$ XcbSurfaceCreateInfoKHR
-> (("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR)
    -> IO SurfaceKHR)
-> IO SurfaceKHR
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (XcbSurfaceCreateInfoKHR
createInfo)
  "pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
    "allocator" ::: Maybe AllocationCallbacks
Nothing -> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ContT SurfaceKHR IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall (f :: * -> *) a. Applicative f => a -> f a
pure "pAllocator" ::: Ptr AllocationCallbacks
forall a. Ptr a
nullPtr
    Just AllocationCallbacks
j -> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO SurfaceKHR)
 -> IO SurfaceKHR)
-> ContT SurfaceKHR IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pAllocator" ::: Ptr AllocationCallbacks) -> IO SurfaceKHR)
  -> IO SurfaceKHR)
 -> ContT SurfaceKHR IO ("pAllocator" ::: Ptr AllocationCallbacks))
-> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO SurfaceKHR)
    -> IO SurfaceKHR)
-> ContT SurfaceKHR IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall a b. (a -> b) -> a -> b
$ AllocationCallbacks
-> (("pAllocator" ::: Ptr AllocationCallbacks) -> IO SurfaceKHR)
-> IO SurfaceKHR
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
  "pSurface" ::: Ptr SurfaceKHR
pPSurface <- ((("pSurface" ::: Ptr SurfaceKHR) -> IO SurfaceKHR)
 -> IO SurfaceKHR)
-> ContT SurfaceKHR IO ("pSurface" ::: Ptr SurfaceKHR)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pSurface" ::: Ptr SurfaceKHR) -> IO SurfaceKHR)
  -> IO SurfaceKHR)
 -> ContT SurfaceKHR IO ("pSurface" ::: Ptr SurfaceKHR))
-> ((("pSurface" ::: Ptr SurfaceKHR) -> IO SurfaceKHR)
    -> IO SurfaceKHR)
-> ContT SurfaceKHR IO ("pSurface" ::: Ptr SurfaceKHR)
forall a b. (a -> b) -> a -> b
$ IO ("pSurface" ::: Ptr SurfaceKHR)
-> (("pSurface" ::: Ptr SurfaceKHR) -> IO ())
-> (("pSurface" ::: Ptr SurfaceKHR) -> IO SurfaceKHR)
-> IO SurfaceKHR
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pSurface" ::: Ptr SurfaceKHR)
forall a. Int -> IO (Ptr a)
callocBytes @SurfaceKHR Int
8) ("pSurface" ::: Ptr SurfaceKHR) -> IO ()
forall a. Ptr a -> IO ()
free
  Result
r <- IO Result -> ContT SurfaceKHR IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT SurfaceKHR IO Result)
-> IO Result -> ContT SurfaceKHR IO Result
forall a b. (a -> b) -> a -> b
$ String -> IO Result -> IO Result
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCreateXcbSurfaceKHR" (Ptr Instance_T
-> ("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pSurface" ::: Ptr SurfaceKHR)
-> IO Result
vkCreateXcbSurfaceKHR' (Instance -> Ptr Instance_T
instanceHandle (Instance
instance')) "pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR
pCreateInfo "pAllocator" ::: Ptr AllocationCallbacks
pAllocator ("pSurface" ::: Ptr SurfaceKHR
pPSurface))
  IO () -> ContT SurfaceKHR IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT SurfaceKHR IO ())
-> IO () -> ContT SurfaceKHR IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
  SurfaceKHR
pSurface <- IO SurfaceKHR -> ContT SurfaceKHR IO SurfaceKHR
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO SurfaceKHR -> ContT SurfaceKHR IO SurfaceKHR)
-> IO SurfaceKHR -> ContT SurfaceKHR IO SurfaceKHR
forall a b. (a -> b) -> a -> b
$ ("pSurface" ::: Ptr SurfaceKHR) -> IO SurfaceKHR
forall a. Storable a => Ptr a -> IO a
peek @SurfaceKHR "pSurface" ::: Ptr SurfaceKHR
pPSurface
  SurfaceKHR -> ContT SurfaceKHR IO SurfaceKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SurfaceKHR -> ContT SurfaceKHR IO SurfaceKHR)
-> SurfaceKHR -> ContT SurfaceKHR IO SurfaceKHR
forall a b. (a -> b) -> a -> b
$ (SurfaceKHR
pSurface)


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkGetPhysicalDeviceXcbPresentationSupportKHR
  :: FunPtr (Ptr PhysicalDevice_T -> Word32 -> Ptr Xcb_connection_t -> Xcb_visualid_t -> IO Bool32) -> Ptr PhysicalDevice_T -> Word32 -> Ptr Xcb_connection_t -> Xcb_visualid_t -> IO Bool32

-- | vkGetPhysicalDeviceXcbPresentationSupportKHR - Query physical device for
-- presentation to X11 server using XCB
--
-- = Description
--
-- This platform-specific function /can/ be called prior to creating a
-- surface.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_KHR_xcb_surface VK_KHR_xcb_surface>,
-- 'Vulkan.Core10.Handles.PhysicalDevice'
getPhysicalDeviceXcbPresentationSupportKHR :: forall io
                                            . (MonadIO io)
                                           => -- | @physicalDevice@ is the physical device.
                                              --
                                              -- #VUID-vkGetPhysicalDeviceXcbPresentationSupportKHR-physicalDevice-parameter#
                                              -- @physicalDevice@ /must/ be a valid
                                              -- 'Vulkan.Core10.Handles.PhysicalDevice' handle
                                              PhysicalDevice
                                           -> -- | @queueFamilyIndex@ is the queue family index.
                                              --
                                              -- #VUID-vkGetPhysicalDeviceXcbPresentationSupportKHR-queueFamilyIndex-01312#
                                              -- @queueFamilyIndex@ /must/ be less than @pQueueFamilyPropertyCount@
                                              -- returned by
                                              -- 'Vulkan.Core10.DeviceInitialization.getPhysicalDeviceQueueFamilyProperties'
                                              -- for the given @physicalDevice@
                                              ("queueFamilyIndex" ::: Word32)
                                           -> -- | @connection@ is a pointer to an @xcb_connection_t@ to the X server.
                                              --
                                              -- #VUID-vkGetPhysicalDeviceXcbPresentationSupportKHR-connection-parameter#
                                              -- @connection@ /must/ be a valid pointer to an @xcb_connection_t@ value
                                              (Ptr Xcb_connection_t)
                                           -> -- | @visual_id@ is an X11 visual (@xcb_visualid_t@).
                                              ("visual_id" ::: Xcb_visualid_t)
                                           -> io (Bool)
getPhysicalDeviceXcbPresentationSupportKHR :: PhysicalDevice
-> ("queueFamilyIndex" ::: Word32)
-> Ptr Xcb_connection_t
-> ("queueFamilyIndex" ::: Word32)
-> io Bool
getPhysicalDeviceXcbPresentationSupportKHR PhysicalDevice
physicalDevice "queueFamilyIndex" ::: Word32
queueFamilyIndex Ptr Xcb_connection_t
connection "queueFamilyIndex" ::: Word32
visual_id = IO Bool -> io Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> io Bool) -> IO Bool -> io Bool
forall a b. (a -> b) -> a -> b
$ do
  let vkGetPhysicalDeviceXcbPresentationSupportKHRPtr :: FunPtr
  (Ptr PhysicalDevice_T
   -> ("queueFamilyIndex" ::: Word32)
   -> Ptr Xcb_connection_t
   -> ("queueFamilyIndex" ::: Word32)
   -> IO Bool32)
vkGetPhysicalDeviceXcbPresentationSupportKHRPtr = InstanceCmds
-> FunPtr
     (Ptr PhysicalDevice_T
      -> ("queueFamilyIndex" ::: Word32)
      -> Ptr Xcb_connection_t
      -> ("queueFamilyIndex" ::: Word32)
      -> IO Bool32)
pVkGetPhysicalDeviceXcbPresentationSupportKHR (PhysicalDevice -> InstanceCmds
instanceCmds (PhysicalDevice
physicalDevice :: PhysicalDevice))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr PhysicalDevice_T
   -> ("queueFamilyIndex" ::: Word32)
   -> Ptr Xcb_connection_t
   -> ("queueFamilyIndex" ::: Word32)
   -> IO Bool32)
vkGetPhysicalDeviceXcbPresentationSupportKHRPtr FunPtr
  (Ptr PhysicalDevice_T
   -> ("queueFamilyIndex" ::: Word32)
   -> Ptr Xcb_connection_t
   -> ("queueFamilyIndex" ::: Word32)
   -> IO Bool32)
-> FunPtr
     (Ptr PhysicalDevice_T
      -> ("queueFamilyIndex" ::: Word32)
      -> Ptr Xcb_connection_t
      -> ("queueFamilyIndex" ::: Word32)
      -> IO Bool32)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr PhysicalDevice_T
   -> ("queueFamilyIndex" ::: Word32)
   -> Ptr Xcb_connection_t
   -> ("queueFamilyIndex" ::: Word32)
   -> IO Bool32)
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkGetPhysicalDeviceXcbPresentationSupportKHR is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetPhysicalDeviceXcbPresentationSupportKHR' :: Ptr PhysicalDevice_T
-> ("queueFamilyIndex" ::: Word32)
-> Ptr Xcb_connection_t
-> ("queueFamilyIndex" ::: Word32)
-> IO Bool32
vkGetPhysicalDeviceXcbPresentationSupportKHR' = FunPtr
  (Ptr PhysicalDevice_T
   -> ("queueFamilyIndex" ::: Word32)
   -> Ptr Xcb_connection_t
   -> ("queueFamilyIndex" ::: Word32)
   -> IO Bool32)
-> Ptr PhysicalDevice_T
-> ("queueFamilyIndex" ::: Word32)
-> Ptr Xcb_connection_t
-> ("queueFamilyIndex" ::: Word32)
-> IO Bool32
mkVkGetPhysicalDeviceXcbPresentationSupportKHR FunPtr
  (Ptr PhysicalDevice_T
   -> ("queueFamilyIndex" ::: Word32)
   -> Ptr Xcb_connection_t
   -> ("queueFamilyIndex" ::: Word32)
   -> IO Bool32)
vkGetPhysicalDeviceXcbPresentationSupportKHRPtr
  Bool32
r <- String -> IO Bool32 -> IO Bool32
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkGetPhysicalDeviceXcbPresentationSupportKHR" (Ptr PhysicalDevice_T
-> ("queueFamilyIndex" ::: Word32)
-> Ptr Xcb_connection_t
-> ("queueFamilyIndex" ::: Word32)
-> IO Bool32
vkGetPhysicalDeviceXcbPresentationSupportKHR' (PhysicalDevice -> Ptr PhysicalDevice_T
physicalDeviceHandle (PhysicalDevice
physicalDevice)) ("queueFamilyIndex" ::: Word32
queueFamilyIndex) (Ptr Xcb_connection_t
connection) ("queueFamilyIndex" ::: Word32
visual_id))
  Bool -> IO Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Bool -> IO Bool) -> Bool -> IO Bool
forall a b. (a -> b) -> a -> b
$ ((Bool32 -> Bool
bool32ToBool Bool32
r))


-- | VkXcbSurfaceCreateInfoKHR - Structure specifying parameters of a newly
-- created Xcb surface object
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_KHR_xcb_surface VK_KHR_xcb_surface>,
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'XcbSurfaceCreateFlagsKHR', 'createXcbSurfaceKHR'
data XcbSurfaceCreateInfoKHR = XcbSurfaceCreateInfoKHR
  { -- | @flags@ is reserved for future use.
    --
    -- #VUID-VkXcbSurfaceCreateInfoKHR-flags-zerobitmask# @flags@ /must/ be @0@
    XcbSurfaceCreateInfoKHR -> XcbSurfaceCreateFlagsKHR
flags :: XcbSurfaceCreateFlagsKHR
  , -- | @connection@ is a pointer to an @xcb_connection_t@ to the X server.
    --
    -- #VUID-VkXcbSurfaceCreateInfoKHR-connection-01310# @connection@ /must/
    -- point to a valid X11 @xcb_connection_t@
    XcbSurfaceCreateInfoKHR -> Ptr Xcb_connection_t
connection :: Ptr Xcb_connection_t
  , -- | @window@ is the @xcb_window_t@ for the X11 window to associate the
    -- surface with.
    --
    -- #VUID-VkXcbSurfaceCreateInfoKHR-window-01311# @window@ /must/ be a valid
    -- X11 @xcb_window_t@
    XcbSurfaceCreateInfoKHR -> "queueFamilyIndex" ::: Word32
window :: Xcb_window_t
  }
  deriving (Typeable, XcbSurfaceCreateInfoKHR -> XcbSurfaceCreateInfoKHR -> Bool
(XcbSurfaceCreateInfoKHR -> XcbSurfaceCreateInfoKHR -> Bool)
-> (XcbSurfaceCreateInfoKHR -> XcbSurfaceCreateInfoKHR -> Bool)
-> Eq XcbSurfaceCreateInfoKHR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: XcbSurfaceCreateInfoKHR -> XcbSurfaceCreateInfoKHR -> Bool
$c/= :: XcbSurfaceCreateInfoKHR -> XcbSurfaceCreateInfoKHR -> Bool
== :: XcbSurfaceCreateInfoKHR -> XcbSurfaceCreateInfoKHR -> Bool
$c== :: XcbSurfaceCreateInfoKHR -> XcbSurfaceCreateInfoKHR -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (XcbSurfaceCreateInfoKHR)
#endif
deriving instance Show XcbSurfaceCreateInfoKHR

instance ToCStruct XcbSurfaceCreateInfoKHR where
  withCStruct :: XcbSurfaceCreateInfoKHR
-> (("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR) -> IO b)
-> IO b
withCStruct XcbSurfaceCreateInfoKHR
x ("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR) -> IO b
f = Int
-> (("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR) -> IO b)
-> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
40 ((("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR) -> IO b) -> IO b)
-> (("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR) -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \"pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR
p -> ("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR)
-> XcbSurfaceCreateInfoKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR
p XcbSurfaceCreateInfoKHR
x (("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR) -> IO b
f "pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR
p)
  pokeCStruct :: ("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR)
-> XcbSurfaceCreateInfoKHR -> IO b -> IO b
pokeCStruct "pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR
p XcbSurfaceCreateInfoKHR{"queueFamilyIndex" ::: Word32
Ptr Xcb_connection_t
XcbSurfaceCreateFlagsKHR
window :: "queueFamilyIndex" ::: Word32
connection :: Ptr Xcb_connection_t
flags :: XcbSurfaceCreateFlagsKHR
$sel:window:XcbSurfaceCreateInfoKHR :: XcbSurfaceCreateInfoKHR -> "queueFamilyIndex" ::: Word32
$sel:connection:XcbSurfaceCreateInfoKHR :: XcbSurfaceCreateInfoKHR -> Ptr Xcb_connection_t
$sel:flags:XcbSurfaceCreateInfoKHR :: XcbSurfaceCreateInfoKHR -> XcbSurfaceCreateFlagsKHR
..} IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR
p ("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_XCB_SURFACE_CREATE_INFO_KHR)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR
p ("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR
p ("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR)
-> Int -> Ptr XcbSurfaceCreateFlagsKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr XcbSurfaceCreateFlagsKHR)) (XcbSurfaceCreateFlagsKHR
flags)
    Ptr (Ptr Xcb_connection_t) -> Ptr Xcb_connection_t -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR
p ("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR)
-> Int -> Ptr (Ptr Xcb_connection_t)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (Ptr Xcb_connection_t))) (Ptr Xcb_connection_t
connection)
    Ptr ("queueFamilyIndex" ::: Word32)
-> ("queueFamilyIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR
p ("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR)
-> Int -> Ptr ("queueFamilyIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Xcb_window_t)) ("queueFamilyIndex" ::: Word32
window)
    IO b
f
  cStructSize :: Int
cStructSize = Int
40
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: ("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR) -> IO b -> IO b
pokeZeroCStruct "pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR
p IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR
p ("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_XCB_SURFACE_CREATE_INFO_KHR)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR
p ("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr (Ptr Xcb_connection_t) -> Ptr Xcb_connection_t -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR
p ("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR)
-> Int -> Ptr (Ptr Xcb_connection_t)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (Ptr Xcb_connection_t))) (Ptr Xcb_connection_t
forall a. Zero a => a
zero)
    Ptr ("queueFamilyIndex" ::: Word32)
-> ("queueFamilyIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR
p ("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR)
-> Int -> Ptr ("queueFamilyIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Xcb_window_t)) ("queueFamilyIndex" ::: Word32
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct XcbSurfaceCreateInfoKHR where
  peekCStruct :: ("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR)
-> IO XcbSurfaceCreateInfoKHR
peekCStruct "pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR
p = do
    XcbSurfaceCreateFlagsKHR
flags <- Ptr XcbSurfaceCreateFlagsKHR -> IO XcbSurfaceCreateFlagsKHR
forall a. Storable a => Ptr a -> IO a
peek @XcbSurfaceCreateFlagsKHR (("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR
p ("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR)
-> Int -> Ptr XcbSurfaceCreateFlagsKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr XcbSurfaceCreateFlagsKHR))
    Ptr Xcb_connection_t
connection <- Ptr (Ptr Xcb_connection_t) -> IO (Ptr Xcb_connection_t)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr Xcb_connection_t) (("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR
p ("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR)
-> Int -> Ptr (Ptr Xcb_connection_t)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (Ptr Xcb_connection_t)))
    "queueFamilyIndex" ::: Word32
window <- Ptr ("queueFamilyIndex" ::: Word32)
-> IO ("queueFamilyIndex" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Xcb_window_t (("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR
p ("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR)
-> Int -> Ptr ("queueFamilyIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Xcb_window_t))
    XcbSurfaceCreateInfoKHR -> IO XcbSurfaceCreateInfoKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (XcbSurfaceCreateInfoKHR -> IO XcbSurfaceCreateInfoKHR)
-> XcbSurfaceCreateInfoKHR -> IO XcbSurfaceCreateInfoKHR
forall a b. (a -> b) -> a -> b
$ XcbSurfaceCreateFlagsKHR
-> Ptr Xcb_connection_t
-> ("queueFamilyIndex" ::: Word32)
-> XcbSurfaceCreateInfoKHR
XcbSurfaceCreateInfoKHR
             XcbSurfaceCreateFlagsKHR
flags Ptr Xcb_connection_t
connection "queueFamilyIndex" ::: Word32
window

instance Storable XcbSurfaceCreateInfoKHR where
  sizeOf :: XcbSurfaceCreateInfoKHR -> Int
sizeOf ~XcbSurfaceCreateInfoKHR
_ = Int
40
  alignment :: XcbSurfaceCreateInfoKHR -> Int
alignment ~XcbSurfaceCreateInfoKHR
_ = Int
8
  peek :: ("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR)
-> IO XcbSurfaceCreateInfoKHR
peek = ("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR)
-> IO XcbSurfaceCreateInfoKHR
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: ("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR)
-> XcbSurfaceCreateInfoKHR -> IO ()
poke "pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR
ptr XcbSurfaceCreateInfoKHR
poked = ("pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR)
-> XcbSurfaceCreateInfoKHR -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pCreateInfo" ::: Ptr XcbSurfaceCreateInfoKHR
ptr XcbSurfaceCreateInfoKHR
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

instance Zero XcbSurfaceCreateInfoKHR where
  zero :: XcbSurfaceCreateInfoKHR
zero = XcbSurfaceCreateFlagsKHR
-> Ptr Xcb_connection_t
-> ("queueFamilyIndex" ::: Word32)
-> XcbSurfaceCreateInfoKHR
XcbSurfaceCreateInfoKHR
           XcbSurfaceCreateFlagsKHR
forall a. Zero a => a
zero
           Ptr Xcb_connection_t
forall a. Zero a => a
zero
           "queueFamilyIndex" ::: Word32
forall a. Zero a => a
zero


-- | VkXcbSurfaceCreateFlagsKHR - Reserved for future use
--
-- = Description
--
-- 'XcbSurfaceCreateFlagsKHR' is a bitmask type for setting a mask, but is
-- currently reserved for future use.
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_KHR_xcb_surface VK_KHR_xcb_surface>,
-- 'XcbSurfaceCreateInfoKHR'
newtype XcbSurfaceCreateFlagsKHR = XcbSurfaceCreateFlagsKHR Flags
  deriving newtype (XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR -> Bool
(XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR -> Bool)
-> (XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR -> Bool)
-> Eq XcbSurfaceCreateFlagsKHR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR -> Bool
$c/= :: XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR -> Bool
== :: XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR -> Bool
$c== :: XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR -> Bool
Eq, Eq XcbSurfaceCreateFlagsKHR
Eq XcbSurfaceCreateFlagsKHR
-> (XcbSurfaceCreateFlagsKHR
    -> XcbSurfaceCreateFlagsKHR -> Ordering)
-> (XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR -> Bool)
-> (XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR -> Bool)
-> (XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR -> Bool)
-> (XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR -> Bool)
-> (XcbSurfaceCreateFlagsKHR
    -> XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR)
-> (XcbSurfaceCreateFlagsKHR
    -> XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR)
-> Ord XcbSurfaceCreateFlagsKHR
XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR -> Bool
XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR -> Ordering
XcbSurfaceCreateFlagsKHR
-> XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: XcbSurfaceCreateFlagsKHR
-> XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR
$cmin :: XcbSurfaceCreateFlagsKHR
-> XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR
max :: XcbSurfaceCreateFlagsKHR
-> XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR
$cmax :: XcbSurfaceCreateFlagsKHR
-> XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR
>= :: XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR -> Bool
$c>= :: XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR -> Bool
> :: XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR -> Bool
$c> :: XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR -> Bool
<= :: XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR -> Bool
$c<= :: XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR -> Bool
< :: XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR -> Bool
$c< :: XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR -> Bool
compare :: XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR -> Ordering
$ccompare :: XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR -> Ordering
$cp1Ord :: Eq XcbSurfaceCreateFlagsKHR
Ord, Ptr b -> Int -> IO XcbSurfaceCreateFlagsKHR
Ptr b -> Int -> XcbSurfaceCreateFlagsKHR -> IO ()
Ptr XcbSurfaceCreateFlagsKHR -> IO XcbSurfaceCreateFlagsKHR
Ptr XcbSurfaceCreateFlagsKHR -> Int -> IO XcbSurfaceCreateFlagsKHR
Ptr XcbSurfaceCreateFlagsKHR
-> Int -> XcbSurfaceCreateFlagsKHR -> IO ()
Ptr XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR -> IO ()
XcbSurfaceCreateFlagsKHR -> Int
(XcbSurfaceCreateFlagsKHR -> Int)
-> (XcbSurfaceCreateFlagsKHR -> Int)
-> (Ptr XcbSurfaceCreateFlagsKHR
    -> Int -> IO XcbSurfaceCreateFlagsKHR)
-> (Ptr XcbSurfaceCreateFlagsKHR
    -> Int -> XcbSurfaceCreateFlagsKHR -> IO ())
-> (forall b. Ptr b -> Int -> IO XcbSurfaceCreateFlagsKHR)
-> (forall b. Ptr b -> Int -> XcbSurfaceCreateFlagsKHR -> IO ())
-> (Ptr XcbSurfaceCreateFlagsKHR -> IO XcbSurfaceCreateFlagsKHR)
-> (Ptr XcbSurfaceCreateFlagsKHR
    -> XcbSurfaceCreateFlagsKHR -> IO ())
-> Storable XcbSurfaceCreateFlagsKHR
forall b. Ptr b -> Int -> IO XcbSurfaceCreateFlagsKHR
forall b. Ptr b -> Int -> XcbSurfaceCreateFlagsKHR -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR -> IO ()
$cpoke :: Ptr XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR -> IO ()
peek :: Ptr XcbSurfaceCreateFlagsKHR -> IO XcbSurfaceCreateFlagsKHR
$cpeek :: Ptr XcbSurfaceCreateFlagsKHR -> IO XcbSurfaceCreateFlagsKHR
pokeByteOff :: Ptr b -> Int -> XcbSurfaceCreateFlagsKHR -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> XcbSurfaceCreateFlagsKHR -> IO ()
peekByteOff :: Ptr b -> Int -> IO XcbSurfaceCreateFlagsKHR
$cpeekByteOff :: forall b. Ptr b -> Int -> IO XcbSurfaceCreateFlagsKHR
pokeElemOff :: Ptr XcbSurfaceCreateFlagsKHR
-> Int -> XcbSurfaceCreateFlagsKHR -> IO ()
$cpokeElemOff :: Ptr XcbSurfaceCreateFlagsKHR
-> Int -> XcbSurfaceCreateFlagsKHR -> IO ()
peekElemOff :: Ptr XcbSurfaceCreateFlagsKHR -> Int -> IO XcbSurfaceCreateFlagsKHR
$cpeekElemOff :: Ptr XcbSurfaceCreateFlagsKHR -> Int -> IO XcbSurfaceCreateFlagsKHR
alignment :: XcbSurfaceCreateFlagsKHR -> Int
$calignment :: XcbSurfaceCreateFlagsKHR -> Int
sizeOf :: XcbSurfaceCreateFlagsKHR -> Int
$csizeOf :: XcbSurfaceCreateFlagsKHR -> Int
Storable, XcbSurfaceCreateFlagsKHR
XcbSurfaceCreateFlagsKHR -> Zero XcbSurfaceCreateFlagsKHR
forall a. a -> Zero a
zero :: XcbSurfaceCreateFlagsKHR
$czero :: XcbSurfaceCreateFlagsKHR
Zero, Eq XcbSurfaceCreateFlagsKHR
XcbSurfaceCreateFlagsKHR
Eq XcbSurfaceCreateFlagsKHR
-> (XcbSurfaceCreateFlagsKHR
    -> XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR)
-> (XcbSurfaceCreateFlagsKHR
    -> XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR)
-> (XcbSurfaceCreateFlagsKHR
    -> XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR)
-> (XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR)
-> (XcbSurfaceCreateFlagsKHR -> Int -> XcbSurfaceCreateFlagsKHR)
-> (XcbSurfaceCreateFlagsKHR -> Int -> XcbSurfaceCreateFlagsKHR)
-> XcbSurfaceCreateFlagsKHR
-> (Int -> XcbSurfaceCreateFlagsKHR)
-> (XcbSurfaceCreateFlagsKHR -> Int -> XcbSurfaceCreateFlagsKHR)
-> (XcbSurfaceCreateFlagsKHR -> Int -> XcbSurfaceCreateFlagsKHR)
-> (XcbSurfaceCreateFlagsKHR -> Int -> XcbSurfaceCreateFlagsKHR)
-> (XcbSurfaceCreateFlagsKHR -> Int -> Bool)
-> (XcbSurfaceCreateFlagsKHR -> Maybe Int)
-> (XcbSurfaceCreateFlagsKHR -> Int)
-> (XcbSurfaceCreateFlagsKHR -> Bool)
-> (XcbSurfaceCreateFlagsKHR -> Int -> XcbSurfaceCreateFlagsKHR)
-> (XcbSurfaceCreateFlagsKHR -> Int -> XcbSurfaceCreateFlagsKHR)
-> (XcbSurfaceCreateFlagsKHR -> Int -> XcbSurfaceCreateFlagsKHR)
-> (XcbSurfaceCreateFlagsKHR -> Int -> XcbSurfaceCreateFlagsKHR)
-> (XcbSurfaceCreateFlagsKHR -> Int -> XcbSurfaceCreateFlagsKHR)
-> (XcbSurfaceCreateFlagsKHR -> Int -> XcbSurfaceCreateFlagsKHR)
-> (XcbSurfaceCreateFlagsKHR -> Int)
-> Bits XcbSurfaceCreateFlagsKHR
Int -> XcbSurfaceCreateFlagsKHR
XcbSurfaceCreateFlagsKHR -> Bool
XcbSurfaceCreateFlagsKHR -> Int
XcbSurfaceCreateFlagsKHR -> Maybe Int
XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR
XcbSurfaceCreateFlagsKHR -> Int -> Bool
XcbSurfaceCreateFlagsKHR -> Int -> XcbSurfaceCreateFlagsKHR
XcbSurfaceCreateFlagsKHR
-> XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR
forall a.
Eq a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
popCount :: XcbSurfaceCreateFlagsKHR -> Int
$cpopCount :: XcbSurfaceCreateFlagsKHR -> Int
rotateR :: XcbSurfaceCreateFlagsKHR -> Int -> XcbSurfaceCreateFlagsKHR
$crotateR :: XcbSurfaceCreateFlagsKHR -> Int -> XcbSurfaceCreateFlagsKHR
rotateL :: XcbSurfaceCreateFlagsKHR -> Int -> XcbSurfaceCreateFlagsKHR
$crotateL :: XcbSurfaceCreateFlagsKHR -> Int -> XcbSurfaceCreateFlagsKHR
unsafeShiftR :: XcbSurfaceCreateFlagsKHR -> Int -> XcbSurfaceCreateFlagsKHR
$cunsafeShiftR :: XcbSurfaceCreateFlagsKHR -> Int -> XcbSurfaceCreateFlagsKHR
shiftR :: XcbSurfaceCreateFlagsKHR -> Int -> XcbSurfaceCreateFlagsKHR
$cshiftR :: XcbSurfaceCreateFlagsKHR -> Int -> XcbSurfaceCreateFlagsKHR
unsafeShiftL :: XcbSurfaceCreateFlagsKHR -> Int -> XcbSurfaceCreateFlagsKHR
$cunsafeShiftL :: XcbSurfaceCreateFlagsKHR -> Int -> XcbSurfaceCreateFlagsKHR
shiftL :: XcbSurfaceCreateFlagsKHR -> Int -> XcbSurfaceCreateFlagsKHR
$cshiftL :: XcbSurfaceCreateFlagsKHR -> Int -> XcbSurfaceCreateFlagsKHR
isSigned :: XcbSurfaceCreateFlagsKHR -> Bool
$cisSigned :: XcbSurfaceCreateFlagsKHR -> Bool
bitSize :: XcbSurfaceCreateFlagsKHR -> Int
$cbitSize :: XcbSurfaceCreateFlagsKHR -> Int
bitSizeMaybe :: XcbSurfaceCreateFlagsKHR -> Maybe Int
$cbitSizeMaybe :: XcbSurfaceCreateFlagsKHR -> Maybe Int
testBit :: XcbSurfaceCreateFlagsKHR -> Int -> Bool
$ctestBit :: XcbSurfaceCreateFlagsKHR -> Int -> Bool
complementBit :: XcbSurfaceCreateFlagsKHR -> Int -> XcbSurfaceCreateFlagsKHR
$ccomplementBit :: XcbSurfaceCreateFlagsKHR -> Int -> XcbSurfaceCreateFlagsKHR
clearBit :: XcbSurfaceCreateFlagsKHR -> Int -> XcbSurfaceCreateFlagsKHR
$cclearBit :: XcbSurfaceCreateFlagsKHR -> Int -> XcbSurfaceCreateFlagsKHR
setBit :: XcbSurfaceCreateFlagsKHR -> Int -> XcbSurfaceCreateFlagsKHR
$csetBit :: XcbSurfaceCreateFlagsKHR -> Int -> XcbSurfaceCreateFlagsKHR
bit :: Int -> XcbSurfaceCreateFlagsKHR
$cbit :: Int -> XcbSurfaceCreateFlagsKHR
zeroBits :: XcbSurfaceCreateFlagsKHR
$czeroBits :: XcbSurfaceCreateFlagsKHR
rotate :: XcbSurfaceCreateFlagsKHR -> Int -> XcbSurfaceCreateFlagsKHR
$crotate :: XcbSurfaceCreateFlagsKHR -> Int -> XcbSurfaceCreateFlagsKHR
shift :: XcbSurfaceCreateFlagsKHR -> Int -> XcbSurfaceCreateFlagsKHR
$cshift :: XcbSurfaceCreateFlagsKHR -> Int -> XcbSurfaceCreateFlagsKHR
complement :: XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR
$ccomplement :: XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR
xor :: XcbSurfaceCreateFlagsKHR
-> XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR
$cxor :: XcbSurfaceCreateFlagsKHR
-> XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR
.|. :: XcbSurfaceCreateFlagsKHR
-> XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR
$c.|. :: XcbSurfaceCreateFlagsKHR
-> XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR
.&. :: XcbSurfaceCreateFlagsKHR
-> XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR
$c.&. :: XcbSurfaceCreateFlagsKHR
-> XcbSurfaceCreateFlagsKHR -> XcbSurfaceCreateFlagsKHR
$cp1Bits :: Eq XcbSurfaceCreateFlagsKHR
Bits, Bits XcbSurfaceCreateFlagsKHR
Bits XcbSurfaceCreateFlagsKHR
-> (XcbSurfaceCreateFlagsKHR -> Int)
-> (XcbSurfaceCreateFlagsKHR -> Int)
-> (XcbSurfaceCreateFlagsKHR -> Int)
-> FiniteBits XcbSurfaceCreateFlagsKHR
XcbSurfaceCreateFlagsKHR -> Int
forall b.
Bits b -> (b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
countTrailingZeros :: XcbSurfaceCreateFlagsKHR -> Int
$ccountTrailingZeros :: XcbSurfaceCreateFlagsKHR -> Int
countLeadingZeros :: XcbSurfaceCreateFlagsKHR -> Int
$ccountLeadingZeros :: XcbSurfaceCreateFlagsKHR -> Int
finiteBitSize :: XcbSurfaceCreateFlagsKHR -> Int
$cfiniteBitSize :: XcbSurfaceCreateFlagsKHR -> Int
$cp1FiniteBits :: Bits XcbSurfaceCreateFlagsKHR
FiniteBits)



conNameXcbSurfaceCreateFlagsKHR :: String
conNameXcbSurfaceCreateFlagsKHR :: String
conNameXcbSurfaceCreateFlagsKHR = String
"XcbSurfaceCreateFlagsKHR"

enumPrefixXcbSurfaceCreateFlagsKHR :: String
enumPrefixXcbSurfaceCreateFlagsKHR :: String
enumPrefixXcbSurfaceCreateFlagsKHR = String
""

showTableXcbSurfaceCreateFlagsKHR :: [(XcbSurfaceCreateFlagsKHR, String)]
showTableXcbSurfaceCreateFlagsKHR :: [(XcbSurfaceCreateFlagsKHR, String)]
showTableXcbSurfaceCreateFlagsKHR = []

instance Show XcbSurfaceCreateFlagsKHR where
  showsPrec :: Int -> XcbSurfaceCreateFlagsKHR -> ShowS
showsPrec = String
-> [(XcbSurfaceCreateFlagsKHR, String)]
-> String
-> (XcbSurfaceCreateFlagsKHR -> "queueFamilyIndex" ::: Word32)
-> (("queueFamilyIndex" ::: Word32) -> ShowS)
-> Int
-> XcbSurfaceCreateFlagsKHR
-> ShowS
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec String
enumPrefixXcbSurfaceCreateFlagsKHR
                            [(XcbSurfaceCreateFlagsKHR, String)]
showTableXcbSurfaceCreateFlagsKHR
                            String
conNameXcbSurfaceCreateFlagsKHR
                            (\(XcbSurfaceCreateFlagsKHR "queueFamilyIndex" ::: Word32
x) -> "queueFamilyIndex" ::: Word32
x)
                            (\"queueFamilyIndex" ::: Word32
x -> String -> ShowS
showString String
"0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ("queueFamilyIndex" ::: Word32) -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex "queueFamilyIndex" ::: Word32
x)

instance Read XcbSurfaceCreateFlagsKHR where
  readPrec :: ReadPrec XcbSurfaceCreateFlagsKHR
readPrec = String
-> [(XcbSurfaceCreateFlagsKHR, String)]
-> String
-> (("queueFamilyIndex" ::: Word32) -> XcbSurfaceCreateFlagsKHR)
-> ReadPrec XcbSurfaceCreateFlagsKHR
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec String
enumPrefixXcbSurfaceCreateFlagsKHR
                          [(XcbSurfaceCreateFlagsKHR, String)]
showTableXcbSurfaceCreateFlagsKHR
                          String
conNameXcbSurfaceCreateFlagsKHR
                          ("queueFamilyIndex" ::: Word32) -> XcbSurfaceCreateFlagsKHR
XcbSurfaceCreateFlagsKHR


type KHR_XCB_SURFACE_SPEC_VERSION = 6

-- No documentation found for TopLevel "VK_KHR_XCB_SURFACE_SPEC_VERSION"
pattern KHR_XCB_SURFACE_SPEC_VERSION :: forall a . Integral a => a
pattern $bKHR_XCB_SURFACE_SPEC_VERSION :: a
$mKHR_XCB_SURFACE_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
KHR_XCB_SURFACE_SPEC_VERSION = 6


type KHR_XCB_SURFACE_EXTENSION_NAME = "VK_KHR_xcb_surface"

-- No documentation found for TopLevel "VK_KHR_XCB_SURFACE_EXTENSION_NAME"
pattern KHR_XCB_SURFACE_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bKHR_XCB_SURFACE_EXTENSION_NAME :: a
$mKHR_XCB_SURFACE_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
KHR_XCB_SURFACE_EXTENSION_NAME = "VK_KHR_xcb_surface"


type Xcb_visualid_t = Word32


type Xcb_window_t = Word32


data Xcb_connection_t