{-# language CPP #-}
-- | = Name
--
-- VK_KHR_wayland_surface - instance extension
--
-- == VK_KHR_wayland_surface
--
-- [__Name String__]
--     @VK_KHR_wayland_surface@
--
-- [__Extension Type__]
--     Instance extension
--
-- [__Registered Extension Number__]
--     7
--
-- [__Revision__]
--     6
--
-- [__Extension and Version Dependencies__]
--
--     -   Requires support for Vulkan 1.0
--
--     -   Requires @VK_KHR_surface@ to be enabled
--
-- [__Contact__]
--
--     -   Jesse Hall
--         <https://github.com/KhronosGroup/Vulkan-Docs/issues/new?body=[VK_KHR_wayland_surface] @critsec%0A*Here describe the issue or question you have about the VK_KHR_wayland_surface extension* >
--
--     -   Ian Elliott
--         <https://github.com/KhronosGroup/Vulkan-Docs/issues/new?body=[VK_KHR_wayland_surface] @ianelliottus%0A*Here describe the issue or question you have about the VK_KHR_wayland_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_wayland_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 a
-- Wayland @wl_surface@, as well as a query to determine support for
-- rendering to a Wayland compositor.
--
-- == New Commands
--
-- -   'createWaylandSurfaceKHR'
--
-- -   'getPhysicalDeviceWaylandPresentationSupportKHR'
--
-- == New Structures
--
-- -   'WaylandSurfaceCreateInfoKHR'
--
-- == New Bitmasks
--
-- -   'WaylandSurfaceCreateFlagsKHR'
--
-- == New Enum Constants
--
-- -   'KHR_WAYLAND_SURFACE_EXTENSION_NAME'
--
-- -   'KHR_WAYLAND_SURFACE_SPEC_VERSION'
--
-- -   Extending 'Vulkan.Core10.Enums.StructureType.StructureType':
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_WAYLAND_SURFACE_CREATE_INFO_KHR'
--
-- == Issues
--
-- 1) Does Wayland need a way to query for compatibility between a
-- particular physical device and a specific Wayland display? This would be
-- a more general query than
-- 'Vulkan.Extensions.VK_KHR_surface.getPhysicalDeviceSurfaceSupportKHR':
-- if the Wayland-specific query returned
-- 'Vulkan.Core10.FundamentalTypes.TRUE' for a
-- ('Vulkan.Core10.Handles.PhysicalDevice', @struct wl_display*@) pair,
-- then the physical device could be assumed to support presentation to any
-- 'Vulkan.Extensions.Handles.SurfaceKHR' for surfaces on the display.
--
-- __RESOLVED__: Yes. 'getPhysicalDeviceWaylandPresentationSupportKHR' was
-- added to address this issue.
--
-- 2) Should we require surfaces created with 'createWaylandSurfaceKHR' to
-- support the 'Vulkan.Extensions.VK_KHR_surface.PRESENT_MODE_MAILBOX_KHR'
-- present mode?
--
-- __RESOLVED__: Yes. Wayland is an inherently mailbox window system and
-- mailbox support is required for some Wayland compositor interactions to
-- work as expected. While handling these interactions may be possible with
-- 'Vulkan.Extensions.VK_KHR_surface.PRESENT_MODE_FIFO_KHR', it is much
-- more difficult to do without deadlock and requiring all Wayland
-- applications to be able to support implementations which only support
-- 'Vulkan.Extensions.VK_KHR_surface.PRESENT_MODE_FIFO_KHR' would be an
-- onerous restriction on application developers.
--
-- == 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 vkGetPhysicalDeviceWaylandPresentationSupportKHR() to
--         resolve issue #1.
--
--     -   Adjusted wording of issue #1 to match the agreed-upon solution.
--
--     -   Renamed “window” parameters to “surface” to match Wayland
--         conventions.
--
-- -   Revision 3, 2015-10-26 (Ian Elliott)
--
--     -   Renamed from VK_EXT_KHR_wayland_surface to
--         VK_KHR_wayland_surface.
--
-- -   Revision 4, 2015-11-03 (Daniel Rakos)
--
--     -   Added allocation callbacks to vkCreateWaylandSurfaceKHR.
--
-- -   Revision 5, 2015-11-28 (Daniel Rakos)
--
--     -   Updated the surface create function to take a pCreateInfo
--         structure.
--
-- -   Revision 6, 2017-02-08 (Jason Ekstrand)
--
--     -   Added the requirement that implementations support
--         'Vulkan.Extensions.VK_KHR_surface.PRESENT_MODE_MAILBOX_KHR'.
--
--     -   Added wording about interactions between
--         'Vulkan.Extensions.VK_KHR_swapchain.queuePresentKHR' and the
--         Wayland requests sent to the compositor.
--
-- == See Also
--
-- 'WaylandSurfaceCreateFlagsKHR', 'WaylandSurfaceCreateInfoKHR',
-- 'createWaylandSurfaceKHR',
-- 'getPhysicalDeviceWaylandPresentationSupportKHR'
--
-- == Document Notes
--
-- For more information, see the
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#VK_KHR_wayland_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_wayland_surface  ( createWaylandSurfaceKHR
                                                 , getPhysicalDeviceWaylandPresentationSupportKHR
                                                 , WaylandSurfaceCreateInfoKHR(..)
                                                 , WaylandSurfaceCreateFlagsKHR(..)
                                                 , KHR_WAYLAND_SURFACE_SPEC_VERSION
                                                 , pattern KHR_WAYLAND_SURFACE_SPEC_VERSION
                                                 , KHR_WAYLAND_SURFACE_EXTENSION_NAME
                                                 , pattern KHR_WAYLAND_SURFACE_EXTENSION_NAME
                                                 , Wl_display
                                                 , Wl_surface
                                                 , SurfaceKHR(..)
                                                 ) where

import Data.Bits (Bits)
import Data.Bits (FiniteBits)
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.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.Core10.Handles (Instance(Instance))
import Vulkan.Dynamic (InstanceCmds(pVkCreateWaylandSurfaceKHR))
import Vulkan.Dynamic (InstanceCmds(pVkGetPhysicalDeviceWaylandPresentationSupportKHR))
import Vulkan.Core10.Handles (Instance_T)
import Vulkan.Core10.Handles (PhysicalDevice)
import Vulkan.Core10.Handles (PhysicalDevice(..))
import Vulkan.Core10.Handles (PhysicalDevice(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_WAYLAND_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" mkVkCreateWaylandSurfaceKHR
  :: FunPtr (Ptr Instance_T -> Ptr WaylandSurfaceCreateInfoKHR -> Ptr AllocationCallbacks -> Ptr SurfaceKHR -> IO Result) -> Ptr Instance_T -> Ptr WaylandSurfaceCreateInfoKHR -> Ptr AllocationCallbacks -> Ptr SurfaceKHR -> IO Result

-- | vkCreateWaylandSurfaceKHR - Create a
-- 'Vulkan.Extensions.Handles.SurfaceKHR' object for a Wayland window
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCreateWaylandSurfaceKHR-instance-parameter# @instance@
--     /must/ be a valid 'Vulkan.Core10.Handles.Instance' handle
--
-- -   #VUID-vkCreateWaylandSurfaceKHR-pCreateInfo-parameter# @pCreateInfo@
--     /must/ be a valid pointer to a valid 'WaylandSurfaceCreateInfoKHR'
--     structure
--
-- -   #VUID-vkCreateWaylandSurfaceKHR-pAllocator-parameter# If
--     @pAllocator@ is not @NULL@, @pAllocator@ /must/ be a valid pointer
--     to a valid 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks'
--     structure
--
-- -   #VUID-vkCreateWaylandSurfaceKHR-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_wayland_surface VK_KHR_wayland_surface>,
-- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks',
-- 'Vulkan.Core10.Handles.Instance',
-- 'Vulkan.Extensions.Handles.SurfaceKHR', 'WaylandSurfaceCreateInfoKHR'
createWaylandSurfaceKHR :: forall io
                         . (MonadIO io)
                        => -- | @instance@ is the instance to associate the surface with.
                           Instance
                        -> -- | @pCreateInfo@ is a pointer to a 'WaylandSurfaceCreateInfoKHR' structure
                           -- containing parameters affecting the creation of the surface object.
                           WaylandSurfaceCreateInfoKHR
                        -> -- | @pAllocator@ is the allocator used for host memory allocated for the
                           -- surface object when there is no more specific allocator available (see
                           -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#memory-allocation Memory Allocation>).
                           ("allocator" ::: Maybe AllocationCallbacks)
                        -> io (SurfaceKHR)
createWaylandSurfaceKHR :: forall (io :: * -> *).
MonadIO io =>
Instance
-> WaylandSurfaceCreateInfoKHR
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io SurfaceKHR
createWaylandSurfaceKHR Instance
instance' WaylandSurfaceCreateInfoKHR
createInfo "allocator" ::: Maybe AllocationCallbacks
allocator = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
  let vkCreateWaylandSurfaceKHRPtr :: FunPtr
  (Ptr Instance_T
   -> ("pCreateInfo" ::: Ptr WaylandSurfaceCreateInfoKHR)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pSurface" ::: Ptr SurfaceKHR)
   -> IO Result)
vkCreateWaylandSurfaceKHRPtr = InstanceCmds
-> FunPtr
     (Ptr Instance_T
      -> ("pCreateInfo" ::: Ptr WaylandSurfaceCreateInfoKHR)
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> ("pSurface" ::: Ptr SurfaceKHR)
      -> IO Result)
pVkCreateWaylandSurfaceKHR (case Instance
instance' of Instance{InstanceCmds
$sel:instanceCmds:Instance :: Instance -> InstanceCmds
instanceCmds :: InstanceCmds
instanceCmds} -> InstanceCmds
instanceCmds)
  forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Instance_T
   -> ("pCreateInfo" ::: Ptr WaylandSurfaceCreateInfoKHR)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pSurface" ::: Ptr SurfaceKHR)
   -> IO Result)
vkCreateWaylandSurfaceKHRPtr forall a. Eq a => a -> a -> Bool
/= forall a. FunPtr a
nullFunPtr) forall a b. (a -> b) -> a -> b
$
    forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkCreateWaylandSurfaceKHR is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkCreateWaylandSurfaceKHR' :: Ptr Instance_T
-> ("pCreateInfo" ::: Ptr WaylandSurfaceCreateInfoKHR)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pSurface" ::: Ptr SurfaceKHR)
-> IO Result
vkCreateWaylandSurfaceKHR' = FunPtr
  (Ptr Instance_T
   -> ("pCreateInfo" ::: Ptr WaylandSurfaceCreateInfoKHR)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pSurface" ::: Ptr SurfaceKHR)
   -> IO Result)
-> Ptr Instance_T
-> ("pCreateInfo" ::: Ptr WaylandSurfaceCreateInfoKHR)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pSurface" ::: Ptr SurfaceKHR)
-> IO Result
mkVkCreateWaylandSurfaceKHR FunPtr
  (Ptr Instance_T
   -> ("pCreateInfo" ::: Ptr WaylandSurfaceCreateInfoKHR)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pSurface" ::: Ptr SurfaceKHR)
   -> IO Result)
vkCreateWaylandSurfaceKHRPtr
  "pCreateInfo" ::: Ptr WaylandSurfaceCreateInfoKHR
pCreateInfo <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (WaylandSurfaceCreateInfoKHR
createInfo)
  "pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
    "allocator" ::: Maybe AllocationCallbacks
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Ptr a
nullPtr
    Just AllocationCallbacks
j -> forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
  "pSurface" ::: Ptr SurfaceKHR
pPSurface <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (forall a. Int -> IO (Ptr a)
callocBytes @SurfaceKHR Int
8) forall a. Ptr a -> IO ()
free
  Result
r <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCreateWaylandSurfaceKHR" (Ptr Instance_T
-> ("pCreateInfo" ::: Ptr WaylandSurfaceCreateInfoKHR)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pSurface" ::: Ptr SurfaceKHR)
-> IO Result
vkCreateWaylandSurfaceKHR'
                                                              (Instance -> Ptr Instance_T
instanceHandle (Instance
instance'))
                                                              "pCreateInfo" ::: Ptr WaylandSurfaceCreateInfoKHR
pCreateInfo
                                                              "pAllocator" ::: Ptr AllocationCallbacks
pAllocator
                                                              ("pSurface" ::: Ptr SurfaceKHR
pPSurface))
  forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
  SurfaceKHR
pSurface <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> IO a
peek @SurfaceKHR "pSurface" ::: Ptr SurfaceKHR
pPSurface
  forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ (SurfaceKHR
pSurface)


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

-- | vkGetPhysicalDeviceWaylandPresentationSupportKHR - Query physical device
-- for presentation to Wayland
--
-- = 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_wayland_surface VK_KHR_wayland_surface>,
-- 'Vulkan.Core10.Handles.PhysicalDevice'
getPhysicalDeviceWaylandPresentationSupportKHR :: forall io
                                                . (MonadIO io)
                                               => -- | @physicalDevice@ is the physical device.
                                                  --
                                                  -- #VUID-vkGetPhysicalDeviceWaylandPresentationSupportKHR-physicalDevice-parameter#
                                                  -- @physicalDevice@ /must/ be a valid
                                                  -- 'Vulkan.Core10.Handles.PhysicalDevice' handle
                                                  PhysicalDevice
                                               -> -- | @queueFamilyIndex@ is the queue family index.
                                                  --
                                                  -- #VUID-vkGetPhysicalDeviceWaylandPresentationSupportKHR-queueFamilyIndex-01306#
                                                  -- @queueFamilyIndex@ /must/ be less than @pQueueFamilyPropertyCount@
                                                  -- returned by
                                                  -- 'Vulkan.Core10.DeviceInitialization.getPhysicalDeviceQueueFamilyProperties'
                                                  -- for the given @physicalDevice@
                                                  ("queueFamilyIndex" ::: Word32)
                                               -> -- | @display@ is a pointer to the @wl_display@ associated with a Wayland
                                                  -- compositor.
                                                  --
                                                  -- #VUID-vkGetPhysicalDeviceWaylandPresentationSupportKHR-display-parameter#
                                                  -- @display@ /must/ be a valid pointer to a @wl_display@ value
                                                  (Ptr Wl_display)
                                               -> io (Bool)
getPhysicalDeviceWaylandPresentationSupportKHR :: forall (io :: * -> *).
MonadIO io =>
PhysicalDevice
-> ("queueFamilyIndex" ::: Word32) -> Ptr Wl_display -> io Bool
getPhysicalDeviceWaylandPresentationSupportKHR PhysicalDevice
physicalDevice
                                                 "queueFamilyIndex" ::: Word32
queueFamilyIndex
                                                 Ptr Wl_display
display = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
  let vkGetPhysicalDeviceWaylandPresentationSupportKHRPtr :: FunPtr
  (Ptr PhysicalDevice_T
   -> ("queueFamilyIndex" ::: Word32) -> Ptr Wl_display -> IO Bool32)
vkGetPhysicalDeviceWaylandPresentationSupportKHRPtr = InstanceCmds
-> FunPtr
     (Ptr PhysicalDevice_T
      -> ("queueFamilyIndex" ::: Word32) -> Ptr Wl_display -> IO Bool32)
pVkGetPhysicalDeviceWaylandPresentationSupportKHR (case PhysicalDevice
physicalDevice of PhysicalDevice{InstanceCmds
$sel:instanceCmds:PhysicalDevice :: PhysicalDevice -> InstanceCmds
instanceCmds :: InstanceCmds
instanceCmds} -> InstanceCmds
instanceCmds)
  forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr PhysicalDevice_T
   -> ("queueFamilyIndex" ::: Word32) -> Ptr Wl_display -> IO Bool32)
vkGetPhysicalDeviceWaylandPresentationSupportKHRPtr forall a. Eq a => a -> a -> Bool
/= forall a. FunPtr a
nullFunPtr) forall a b. (a -> b) -> a -> b
$
    forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkGetPhysicalDeviceWaylandPresentationSupportKHR is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkGetPhysicalDeviceWaylandPresentationSupportKHR' :: Ptr PhysicalDevice_T
-> ("queueFamilyIndex" ::: Word32) -> Ptr Wl_display -> IO Bool32
vkGetPhysicalDeviceWaylandPresentationSupportKHR' = FunPtr
  (Ptr PhysicalDevice_T
   -> ("queueFamilyIndex" ::: Word32) -> Ptr Wl_display -> IO Bool32)
-> Ptr PhysicalDevice_T
-> ("queueFamilyIndex" ::: Word32)
-> Ptr Wl_display
-> IO Bool32
mkVkGetPhysicalDeviceWaylandPresentationSupportKHR FunPtr
  (Ptr PhysicalDevice_T
   -> ("queueFamilyIndex" ::: Word32) -> Ptr Wl_display -> IO Bool32)
vkGetPhysicalDeviceWaylandPresentationSupportKHRPtr
  Bool32
r <- forall a. String -> IO a -> IO a
traceAroundEvent String
"vkGetPhysicalDeviceWaylandPresentationSupportKHR" (Ptr PhysicalDevice_T
-> ("queueFamilyIndex" ::: Word32) -> Ptr Wl_display -> IO Bool32
vkGetPhysicalDeviceWaylandPresentationSupportKHR'
                                                                              (PhysicalDevice -> Ptr PhysicalDevice_T
physicalDeviceHandle (PhysicalDevice
physicalDevice))
                                                                              ("queueFamilyIndex" ::: Word32
queueFamilyIndex)
                                                                              (Ptr Wl_display
display))
  forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ((Bool32 -> Bool
bool32ToBool Bool32
r))


-- | VkWaylandSurfaceCreateInfoKHR - Structure specifying parameters of a
-- newly created Wayland surface object
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_KHR_wayland_surface VK_KHR_wayland_surface>,
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'WaylandSurfaceCreateFlagsKHR', 'createWaylandSurfaceKHR'
data WaylandSurfaceCreateInfoKHR = WaylandSurfaceCreateInfoKHR
  { -- | @flags@ is reserved for future use.
    --
    -- #VUID-VkWaylandSurfaceCreateInfoKHR-flags-zerobitmask# @flags@ /must/ be
    -- @0@
    WaylandSurfaceCreateInfoKHR -> WaylandSurfaceCreateFlagsKHR
flags :: WaylandSurfaceCreateFlagsKHR
  , -- | @display@ and @surface@ are pointers to the Wayland @wl_display@ and
    -- @wl_surface@ to associate the surface with.
    --
    -- #VUID-VkWaylandSurfaceCreateInfoKHR-display-01304# @display@ /must/
    -- point to a valid Wayland @wl_display@
    WaylandSurfaceCreateInfoKHR -> Ptr Wl_display
display :: Ptr Wl_display
  , -- | #VUID-VkWaylandSurfaceCreateInfoKHR-surface-01305# @surface@ /must/
    -- point to a valid Wayland @wl_surface@
    WaylandSurfaceCreateInfoKHR -> Ptr Wl_surface
surface :: Ptr Wl_surface
  }
  deriving (Typeable, WaylandSurfaceCreateInfoKHR -> WaylandSurfaceCreateInfoKHR -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WaylandSurfaceCreateInfoKHR -> WaylandSurfaceCreateInfoKHR -> Bool
$c/= :: WaylandSurfaceCreateInfoKHR -> WaylandSurfaceCreateInfoKHR -> Bool
== :: WaylandSurfaceCreateInfoKHR -> WaylandSurfaceCreateInfoKHR -> Bool
$c== :: WaylandSurfaceCreateInfoKHR -> WaylandSurfaceCreateInfoKHR -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (WaylandSurfaceCreateInfoKHR)
#endif
deriving instance Show WaylandSurfaceCreateInfoKHR

instance ToCStruct WaylandSurfaceCreateInfoKHR where
  withCStruct :: forall b.
WaylandSurfaceCreateInfoKHR
-> (("pCreateInfo" ::: Ptr WaylandSurfaceCreateInfoKHR) -> IO b)
-> IO b
withCStruct WaylandSurfaceCreateInfoKHR
x ("pCreateInfo" ::: Ptr WaylandSurfaceCreateInfoKHR) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
40 forall a b. (a -> b) -> a -> b
$ \"pCreateInfo" ::: Ptr WaylandSurfaceCreateInfoKHR
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pCreateInfo" ::: Ptr WaylandSurfaceCreateInfoKHR
p WaylandSurfaceCreateInfoKHR
x (("pCreateInfo" ::: Ptr WaylandSurfaceCreateInfoKHR) -> IO b
f "pCreateInfo" ::: Ptr WaylandSurfaceCreateInfoKHR
p)
  pokeCStruct :: forall b.
("pCreateInfo" ::: Ptr WaylandSurfaceCreateInfoKHR)
-> WaylandSurfaceCreateInfoKHR -> IO b -> IO b
pokeCStruct "pCreateInfo" ::: Ptr WaylandSurfaceCreateInfoKHR
p WaylandSurfaceCreateInfoKHR{Ptr Wl_display
Ptr Wl_surface
WaylandSurfaceCreateFlagsKHR
surface :: Ptr Wl_surface
display :: Ptr Wl_display
flags :: WaylandSurfaceCreateFlagsKHR
$sel:surface:WaylandSurfaceCreateInfoKHR :: WaylandSurfaceCreateInfoKHR -> Ptr Wl_surface
$sel:display:WaylandSurfaceCreateInfoKHR :: WaylandSurfaceCreateInfoKHR -> Ptr Wl_display
$sel:flags:WaylandSurfaceCreateInfoKHR :: WaylandSurfaceCreateInfoKHR -> WaylandSurfaceCreateFlagsKHR
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr WaylandSurfaceCreateInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_WAYLAND_SURFACE_CREATE_INFO_KHR)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr WaylandSurfaceCreateInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr WaylandSurfaceCreateInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr WaylandSurfaceCreateFlagsKHR)) (WaylandSurfaceCreateFlagsKHR
flags)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr WaylandSurfaceCreateInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (Ptr Wl_display))) (Ptr Wl_display
display)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr WaylandSurfaceCreateInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr (Ptr Wl_surface))) (Ptr Wl_surface
surface)
    IO b
f
  cStructSize :: Int
cStructSize = Int
40
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
("pCreateInfo" ::: Ptr WaylandSurfaceCreateInfoKHR) -> IO b -> IO b
pokeZeroCStruct "pCreateInfo" ::: Ptr WaylandSurfaceCreateInfoKHR
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr WaylandSurfaceCreateInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_WAYLAND_SURFACE_CREATE_INFO_KHR)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr WaylandSurfaceCreateInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr WaylandSurfaceCreateInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (Ptr Wl_display))) (forall a. Zero a => a
zero)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr WaylandSurfaceCreateInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr (Ptr Wl_surface))) (forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct WaylandSurfaceCreateInfoKHR where
  peekCStruct :: ("pCreateInfo" ::: Ptr WaylandSurfaceCreateInfoKHR)
-> IO WaylandSurfaceCreateInfoKHR
peekCStruct "pCreateInfo" ::: Ptr WaylandSurfaceCreateInfoKHR
p = do
    WaylandSurfaceCreateFlagsKHR
flags <- forall a. Storable a => Ptr a -> IO a
peek @WaylandSurfaceCreateFlagsKHR (("pCreateInfo" ::: Ptr WaylandSurfaceCreateInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr WaylandSurfaceCreateFlagsKHR))
    Ptr Wl_display
display <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr Wl_display) (("pCreateInfo" ::: Ptr WaylandSurfaceCreateInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (Ptr Wl_display)))
    Ptr Wl_surface
surface <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr Wl_surface) (("pCreateInfo" ::: Ptr WaylandSurfaceCreateInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr (Ptr Wl_surface)))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ WaylandSurfaceCreateFlagsKHR
-> Ptr Wl_display -> Ptr Wl_surface -> WaylandSurfaceCreateInfoKHR
WaylandSurfaceCreateInfoKHR
             WaylandSurfaceCreateFlagsKHR
flags Ptr Wl_display
display Ptr Wl_surface
surface

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

instance Zero WaylandSurfaceCreateInfoKHR where
  zero :: WaylandSurfaceCreateInfoKHR
zero = WaylandSurfaceCreateFlagsKHR
-> Ptr Wl_display -> Ptr Wl_surface -> WaylandSurfaceCreateInfoKHR
WaylandSurfaceCreateInfoKHR
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero


-- | VkWaylandSurfaceCreateFlagsKHR - Reserved for future use
--
-- = Description
--
-- 'WaylandSurfaceCreateFlagsKHR' 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_wayland_surface VK_KHR_wayland_surface>,
-- 'WaylandSurfaceCreateInfoKHR'
newtype WaylandSurfaceCreateFlagsKHR = WaylandSurfaceCreateFlagsKHR Flags
  deriving newtype (WaylandSurfaceCreateFlagsKHR
-> WaylandSurfaceCreateFlagsKHR -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WaylandSurfaceCreateFlagsKHR
-> WaylandSurfaceCreateFlagsKHR -> Bool
$c/= :: WaylandSurfaceCreateFlagsKHR
-> WaylandSurfaceCreateFlagsKHR -> Bool
== :: WaylandSurfaceCreateFlagsKHR
-> WaylandSurfaceCreateFlagsKHR -> Bool
$c== :: WaylandSurfaceCreateFlagsKHR
-> WaylandSurfaceCreateFlagsKHR -> Bool
Eq, Eq WaylandSurfaceCreateFlagsKHR
WaylandSurfaceCreateFlagsKHR
-> WaylandSurfaceCreateFlagsKHR -> Bool
WaylandSurfaceCreateFlagsKHR
-> WaylandSurfaceCreateFlagsKHR -> Ordering
WaylandSurfaceCreateFlagsKHR
-> WaylandSurfaceCreateFlagsKHR -> WaylandSurfaceCreateFlagsKHR
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 :: WaylandSurfaceCreateFlagsKHR
-> WaylandSurfaceCreateFlagsKHR -> WaylandSurfaceCreateFlagsKHR
$cmin :: WaylandSurfaceCreateFlagsKHR
-> WaylandSurfaceCreateFlagsKHR -> WaylandSurfaceCreateFlagsKHR
max :: WaylandSurfaceCreateFlagsKHR
-> WaylandSurfaceCreateFlagsKHR -> WaylandSurfaceCreateFlagsKHR
$cmax :: WaylandSurfaceCreateFlagsKHR
-> WaylandSurfaceCreateFlagsKHR -> WaylandSurfaceCreateFlagsKHR
>= :: WaylandSurfaceCreateFlagsKHR
-> WaylandSurfaceCreateFlagsKHR -> Bool
$c>= :: WaylandSurfaceCreateFlagsKHR
-> WaylandSurfaceCreateFlagsKHR -> Bool
> :: WaylandSurfaceCreateFlagsKHR
-> WaylandSurfaceCreateFlagsKHR -> Bool
$c> :: WaylandSurfaceCreateFlagsKHR
-> WaylandSurfaceCreateFlagsKHR -> Bool
<= :: WaylandSurfaceCreateFlagsKHR
-> WaylandSurfaceCreateFlagsKHR -> Bool
$c<= :: WaylandSurfaceCreateFlagsKHR
-> WaylandSurfaceCreateFlagsKHR -> Bool
< :: WaylandSurfaceCreateFlagsKHR
-> WaylandSurfaceCreateFlagsKHR -> Bool
$c< :: WaylandSurfaceCreateFlagsKHR
-> WaylandSurfaceCreateFlagsKHR -> Bool
compare :: WaylandSurfaceCreateFlagsKHR
-> WaylandSurfaceCreateFlagsKHR -> Ordering
$ccompare :: WaylandSurfaceCreateFlagsKHR
-> WaylandSurfaceCreateFlagsKHR -> Ordering
Ord, Ptr WaylandSurfaceCreateFlagsKHR -> IO WaylandSurfaceCreateFlagsKHR
Ptr WaylandSurfaceCreateFlagsKHR
-> Int -> IO WaylandSurfaceCreateFlagsKHR
Ptr WaylandSurfaceCreateFlagsKHR
-> Int -> WaylandSurfaceCreateFlagsKHR -> IO ()
Ptr WaylandSurfaceCreateFlagsKHR
-> WaylandSurfaceCreateFlagsKHR -> IO ()
WaylandSurfaceCreateFlagsKHR -> Int
forall b. Ptr b -> Int -> IO WaylandSurfaceCreateFlagsKHR
forall b. Ptr b -> Int -> WaylandSurfaceCreateFlagsKHR -> 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 WaylandSurfaceCreateFlagsKHR
-> WaylandSurfaceCreateFlagsKHR -> IO ()
$cpoke :: Ptr WaylandSurfaceCreateFlagsKHR
-> WaylandSurfaceCreateFlagsKHR -> IO ()
peek :: Ptr WaylandSurfaceCreateFlagsKHR -> IO WaylandSurfaceCreateFlagsKHR
$cpeek :: Ptr WaylandSurfaceCreateFlagsKHR -> IO WaylandSurfaceCreateFlagsKHR
pokeByteOff :: forall b. Ptr b -> Int -> WaylandSurfaceCreateFlagsKHR -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> WaylandSurfaceCreateFlagsKHR -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO WaylandSurfaceCreateFlagsKHR
$cpeekByteOff :: forall b. Ptr b -> Int -> IO WaylandSurfaceCreateFlagsKHR
pokeElemOff :: Ptr WaylandSurfaceCreateFlagsKHR
-> Int -> WaylandSurfaceCreateFlagsKHR -> IO ()
$cpokeElemOff :: Ptr WaylandSurfaceCreateFlagsKHR
-> Int -> WaylandSurfaceCreateFlagsKHR -> IO ()
peekElemOff :: Ptr WaylandSurfaceCreateFlagsKHR
-> Int -> IO WaylandSurfaceCreateFlagsKHR
$cpeekElemOff :: Ptr WaylandSurfaceCreateFlagsKHR
-> Int -> IO WaylandSurfaceCreateFlagsKHR
alignment :: WaylandSurfaceCreateFlagsKHR -> Int
$calignment :: WaylandSurfaceCreateFlagsKHR -> Int
sizeOf :: WaylandSurfaceCreateFlagsKHR -> Int
$csizeOf :: WaylandSurfaceCreateFlagsKHR -> Int
Storable, WaylandSurfaceCreateFlagsKHR
forall a. a -> Zero a
zero :: WaylandSurfaceCreateFlagsKHR
$czero :: WaylandSurfaceCreateFlagsKHR
Zero, Eq WaylandSurfaceCreateFlagsKHR
WaylandSurfaceCreateFlagsKHR
Int -> WaylandSurfaceCreateFlagsKHR
WaylandSurfaceCreateFlagsKHR -> Bool
WaylandSurfaceCreateFlagsKHR -> Int
WaylandSurfaceCreateFlagsKHR -> Maybe Int
WaylandSurfaceCreateFlagsKHR -> WaylandSurfaceCreateFlagsKHR
WaylandSurfaceCreateFlagsKHR -> Int -> Bool
WaylandSurfaceCreateFlagsKHR -> Int -> WaylandSurfaceCreateFlagsKHR
WaylandSurfaceCreateFlagsKHR
-> WaylandSurfaceCreateFlagsKHR -> WaylandSurfaceCreateFlagsKHR
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 :: WaylandSurfaceCreateFlagsKHR -> Int
$cpopCount :: WaylandSurfaceCreateFlagsKHR -> Int
rotateR :: WaylandSurfaceCreateFlagsKHR -> Int -> WaylandSurfaceCreateFlagsKHR
$crotateR :: WaylandSurfaceCreateFlagsKHR -> Int -> WaylandSurfaceCreateFlagsKHR
rotateL :: WaylandSurfaceCreateFlagsKHR -> Int -> WaylandSurfaceCreateFlagsKHR
$crotateL :: WaylandSurfaceCreateFlagsKHR -> Int -> WaylandSurfaceCreateFlagsKHR
unsafeShiftR :: WaylandSurfaceCreateFlagsKHR -> Int -> WaylandSurfaceCreateFlagsKHR
$cunsafeShiftR :: WaylandSurfaceCreateFlagsKHR -> Int -> WaylandSurfaceCreateFlagsKHR
shiftR :: WaylandSurfaceCreateFlagsKHR -> Int -> WaylandSurfaceCreateFlagsKHR
$cshiftR :: WaylandSurfaceCreateFlagsKHR -> Int -> WaylandSurfaceCreateFlagsKHR
unsafeShiftL :: WaylandSurfaceCreateFlagsKHR -> Int -> WaylandSurfaceCreateFlagsKHR
$cunsafeShiftL :: WaylandSurfaceCreateFlagsKHR -> Int -> WaylandSurfaceCreateFlagsKHR
shiftL :: WaylandSurfaceCreateFlagsKHR -> Int -> WaylandSurfaceCreateFlagsKHR
$cshiftL :: WaylandSurfaceCreateFlagsKHR -> Int -> WaylandSurfaceCreateFlagsKHR
isSigned :: WaylandSurfaceCreateFlagsKHR -> Bool
$cisSigned :: WaylandSurfaceCreateFlagsKHR -> Bool
bitSize :: WaylandSurfaceCreateFlagsKHR -> Int
$cbitSize :: WaylandSurfaceCreateFlagsKHR -> Int
bitSizeMaybe :: WaylandSurfaceCreateFlagsKHR -> Maybe Int
$cbitSizeMaybe :: WaylandSurfaceCreateFlagsKHR -> Maybe Int
testBit :: WaylandSurfaceCreateFlagsKHR -> Int -> Bool
$ctestBit :: WaylandSurfaceCreateFlagsKHR -> Int -> Bool
complementBit :: WaylandSurfaceCreateFlagsKHR -> Int -> WaylandSurfaceCreateFlagsKHR
$ccomplementBit :: WaylandSurfaceCreateFlagsKHR -> Int -> WaylandSurfaceCreateFlagsKHR
clearBit :: WaylandSurfaceCreateFlagsKHR -> Int -> WaylandSurfaceCreateFlagsKHR
$cclearBit :: WaylandSurfaceCreateFlagsKHR -> Int -> WaylandSurfaceCreateFlagsKHR
setBit :: WaylandSurfaceCreateFlagsKHR -> Int -> WaylandSurfaceCreateFlagsKHR
$csetBit :: WaylandSurfaceCreateFlagsKHR -> Int -> WaylandSurfaceCreateFlagsKHR
bit :: Int -> WaylandSurfaceCreateFlagsKHR
$cbit :: Int -> WaylandSurfaceCreateFlagsKHR
zeroBits :: WaylandSurfaceCreateFlagsKHR
$czeroBits :: WaylandSurfaceCreateFlagsKHR
rotate :: WaylandSurfaceCreateFlagsKHR -> Int -> WaylandSurfaceCreateFlagsKHR
$crotate :: WaylandSurfaceCreateFlagsKHR -> Int -> WaylandSurfaceCreateFlagsKHR
shift :: WaylandSurfaceCreateFlagsKHR -> Int -> WaylandSurfaceCreateFlagsKHR
$cshift :: WaylandSurfaceCreateFlagsKHR -> Int -> WaylandSurfaceCreateFlagsKHR
complement :: WaylandSurfaceCreateFlagsKHR -> WaylandSurfaceCreateFlagsKHR
$ccomplement :: WaylandSurfaceCreateFlagsKHR -> WaylandSurfaceCreateFlagsKHR
xor :: WaylandSurfaceCreateFlagsKHR
-> WaylandSurfaceCreateFlagsKHR -> WaylandSurfaceCreateFlagsKHR
$cxor :: WaylandSurfaceCreateFlagsKHR
-> WaylandSurfaceCreateFlagsKHR -> WaylandSurfaceCreateFlagsKHR
.|. :: WaylandSurfaceCreateFlagsKHR
-> WaylandSurfaceCreateFlagsKHR -> WaylandSurfaceCreateFlagsKHR
$c.|. :: WaylandSurfaceCreateFlagsKHR
-> WaylandSurfaceCreateFlagsKHR -> WaylandSurfaceCreateFlagsKHR
.&. :: WaylandSurfaceCreateFlagsKHR
-> WaylandSurfaceCreateFlagsKHR -> WaylandSurfaceCreateFlagsKHR
$c.&. :: WaylandSurfaceCreateFlagsKHR
-> WaylandSurfaceCreateFlagsKHR -> WaylandSurfaceCreateFlagsKHR
Bits, Bits WaylandSurfaceCreateFlagsKHR
WaylandSurfaceCreateFlagsKHR -> Int
forall b.
Bits b -> (b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
countTrailingZeros :: WaylandSurfaceCreateFlagsKHR -> Int
$ccountTrailingZeros :: WaylandSurfaceCreateFlagsKHR -> Int
countLeadingZeros :: WaylandSurfaceCreateFlagsKHR -> Int
$ccountLeadingZeros :: WaylandSurfaceCreateFlagsKHR -> Int
finiteBitSize :: WaylandSurfaceCreateFlagsKHR -> Int
$cfiniteBitSize :: WaylandSurfaceCreateFlagsKHR -> Int
FiniteBits)

conNameWaylandSurfaceCreateFlagsKHR :: String
conNameWaylandSurfaceCreateFlagsKHR :: String
conNameWaylandSurfaceCreateFlagsKHR = String
"WaylandSurfaceCreateFlagsKHR"

enumPrefixWaylandSurfaceCreateFlagsKHR :: String
enumPrefixWaylandSurfaceCreateFlagsKHR :: String
enumPrefixWaylandSurfaceCreateFlagsKHR = String
""

showTableWaylandSurfaceCreateFlagsKHR :: [(WaylandSurfaceCreateFlagsKHR, String)]
showTableWaylandSurfaceCreateFlagsKHR :: [(WaylandSurfaceCreateFlagsKHR, String)]
showTableWaylandSurfaceCreateFlagsKHR = []

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

instance Read WaylandSurfaceCreateFlagsKHR where
  readPrec :: ReadPrec WaylandSurfaceCreateFlagsKHR
readPrec =
    forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
      String
enumPrefixWaylandSurfaceCreateFlagsKHR
      [(WaylandSurfaceCreateFlagsKHR, String)]
showTableWaylandSurfaceCreateFlagsKHR
      String
conNameWaylandSurfaceCreateFlagsKHR
      ("queueFamilyIndex" ::: Word32) -> WaylandSurfaceCreateFlagsKHR
WaylandSurfaceCreateFlagsKHR

type KHR_WAYLAND_SURFACE_SPEC_VERSION = 6

-- No documentation found for TopLevel "VK_KHR_WAYLAND_SURFACE_SPEC_VERSION"
pattern KHR_WAYLAND_SURFACE_SPEC_VERSION :: forall a . Integral a => a
pattern $bKHR_WAYLAND_SURFACE_SPEC_VERSION :: forall a. Integral a => a
$mKHR_WAYLAND_SURFACE_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
KHR_WAYLAND_SURFACE_SPEC_VERSION = 6


type KHR_WAYLAND_SURFACE_EXTENSION_NAME = "VK_KHR_wayland_surface"

-- No documentation found for TopLevel "VK_KHR_WAYLAND_SURFACE_EXTENSION_NAME"
pattern KHR_WAYLAND_SURFACE_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bKHR_WAYLAND_SURFACE_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mKHR_WAYLAND_SURFACE_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
KHR_WAYLAND_SURFACE_EXTENSION_NAME = "VK_KHR_wayland_surface"


data Wl_display


data Wl_surface