{-# language CPP #-}
module Vulkan.Extensions.VK_KHR_swapchain  ( createSwapchainKHR
                                           , withSwapchainKHR
                                           , destroySwapchainKHR
                                           , getSwapchainImagesKHR
                                           , acquireNextImageKHR
                                           , acquireNextImageKHRSafe
                                           , queuePresentKHR
                                           , getDeviceGroupPresentCapabilitiesKHR
                                           , getDeviceGroupSurfacePresentModesKHR
                                           , acquireNextImage2KHR
                                           , acquireNextImage2KHRSafe
                                           , getPhysicalDevicePresentRectanglesKHR
                                           , SwapchainCreateInfoKHR(..)
                                           , PresentInfoKHR(..)
                                           , DeviceGroupPresentCapabilitiesKHR(..)
                                           , ImageSwapchainCreateInfoKHR(..)
                                           , BindImageMemorySwapchainInfoKHR(..)
                                           , AcquireNextImageInfoKHR(..)
                                           , DeviceGroupPresentInfoKHR(..)
                                           , DeviceGroupSwapchainCreateInfoKHR(..)
                                           , DeviceGroupPresentModeFlagBitsKHR( DEVICE_GROUP_PRESENT_MODE_LOCAL_BIT_KHR
                                                                              , DEVICE_GROUP_PRESENT_MODE_REMOTE_BIT_KHR
                                                                              , DEVICE_GROUP_PRESENT_MODE_SUM_BIT_KHR
                                                                              , DEVICE_GROUP_PRESENT_MODE_LOCAL_MULTI_DEVICE_BIT_KHR
                                                                              , ..
                                                                              )
                                           , DeviceGroupPresentModeFlagsKHR
                                           , SwapchainCreateFlagBitsKHR( SWAPCHAIN_CREATE_MUTABLE_FORMAT_BIT_KHR
                                                                       , SWAPCHAIN_CREATE_SPLIT_INSTANCE_BIND_REGIONS_BIT_KHR
                                                                       , SWAPCHAIN_CREATE_PROTECTED_BIT_KHR
                                                                       , ..
                                                                       )
                                           , SwapchainCreateFlagsKHR
                                           , KHR_SWAPCHAIN_SPEC_VERSION
                                           , pattern KHR_SWAPCHAIN_SPEC_VERSION
                                           , KHR_SWAPCHAIN_EXTENSION_NAME
                                           , pattern KHR_SWAPCHAIN_EXTENSION_NAME
                                           , SurfaceKHR(..)
                                           , SwapchainKHR(..)
                                           , PresentModeKHR(..)
                                           , ColorSpaceKHR(..)
                                           , CompositeAlphaFlagBitsKHR(..)
                                           , CompositeAlphaFlagsKHR
                                           , SurfaceTransformFlagBitsKHR(..)
                                           , SurfaceTransformFlagsKHR
                                           ) where

import Vulkan.CStruct.Utils (FixedArray)
import Control.Exception.Base (bracket)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Data.Typeable (eqT)
import Foreign.Marshal.Alloc (allocaBytesAligned)
import Foreign.Marshal.Alloc (callocBytes)
import Foreign.Marshal.Alloc (free)
import GHC.Base (when)
import GHC.IO (throwIO)
import GHC.Ptr (castPtr)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import GHC.Read (choose)
import GHC.Read (expectP)
import GHC.Read (parens)
import GHC.Show (showParen)
import GHC.Show (showString)
import Numeric (showHex)
import Text.ParserCombinators.ReadPrec ((+++))
import Text.ParserCombinators.ReadPrec (prec)
import Text.ParserCombinators.ReadPrec (step)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import Data.Vector (generateM)
import qualified Data.Vector (imapM_)
import qualified Data.Vector (length)
import Control.Monad.IO.Class (MonadIO)
import Data.Bits (Bits)
import Data.String (IsString)
import Data.Type.Equality ((:~:)(Refl))
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 Data.Word (Word32)
import Data.Word (Word64)
import Text.Read.Lex (Lexeme(Ident))
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Data.Vector (Vector)
import Vulkan.CStruct.Utils (advancePtrBytes)
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.CStruct.Extends (forgetExtensions)
import Vulkan.CStruct.Utils (lowerArrayPtr)
import Vulkan.NamedType ((:::))
import Vulkan.Core10.AllocationCallbacks (AllocationCallbacks)
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.CStruct.Extends (Chain)
import Vulkan.Extensions.VK_KHR_surface (ColorSpaceKHR)
import Vulkan.Extensions.VK_KHR_surface (CompositeAlphaFlagBitsKHR)
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Dynamic (DeviceCmds(pVkAcquireNextImage2KHR))
import Vulkan.Dynamic (DeviceCmds(pVkAcquireNextImageKHR))
import Vulkan.Dynamic (DeviceCmds(pVkCreateSwapchainKHR))
import Vulkan.Dynamic (DeviceCmds(pVkDestroySwapchainKHR))
import Vulkan.Dynamic (DeviceCmds(pVkGetDeviceGroupPresentCapabilitiesKHR))
import Vulkan.Dynamic (DeviceCmds(pVkGetDeviceGroupSurfacePresentModesKHR))
import Vulkan.Dynamic (DeviceCmds(pVkGetSwapchainImagesKHR))
import Vulkan.Dynamic (DeviceCmds(pVkQueuePresentKHR))
import Vulkan.Core10.Handles (Device_T)
import {-# SOURCE #-} Vulkan.Extensions.VK_KHR_display_swapchain (DisplayPresentInfoKHR)
import Vulkan.CStruct.Extends (Extends)
import Vulkan.CStruct.Extends (Extendss)
import Vulkan.CStruct.Extends (Extensible(..))
import Vulkan.Core10.FundamentalTypes (Extent2D)
import Vulkan.Core10.Handles (Fence)
import Vulkan.Core10.Handles (Fence(..))
import Vulkan.Core10.FundamentalTypes (Flags)
import Vulkan.Core10.Enums.Format (Format)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.Handles (Image)
import Vulkan.Core10.Handles (Image(..))
import {-# SOURCE #-} Vulkan.Core12.Promoted_From_VK_KHR_image_format_list (ImageFormatListCreateInfo)
import Vulkan.Core10.Enums.ImageUsageFlagBits (ImageUsageFlags)
import Vulkan.Dynamic (InstanceCmds(pVkGetPhysicalDevicePresentRectanglesKHR))
import Vulkan.Core10.APIConstants (MAX_DEVICE_GROUP_SIZE)
import Vulkan.CStruct.Extends (PeekChain)
import Vulkan.CStruct.Extends (PeekChain(..))
import Vulkan.Core10.Handles (PhysicalDevice)
import Vulkan.Core10.Handles (PhysicalDevice(..))
import Vulkan.Core10.Handles (PhysicalDevice_T)
import Vulkan.CStruct.Extends (PokeChain)
import Vulkan.CStruct.Extends (PokeChain(..))
import {-# SOURCE #-} Vulkan.Extensions.VK_GGP_frame_token (PresentFrameTokenGGP)
import Vulkan.Extensions.VK_KHR_surface (PresentModeKHR)
import {-# SOURCE #-} Vulkan.Extensions.VK_KHR_incremental_present (PresentRegionsKHR)
import {-# SOURCE #-} Vulkan.Extensions.VK_GOOGLE_display_timing (PresentTimesInfoGOOGLE)
import Vulkan.Core10.Handles (Queue)
import Vulkan.Core10.Handles (Queue(..))
import Vulkan.Core10.Handles (Queue_T)
import Vulkan.Core10.FundamentalTypes (Rect2D)
import Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.Core10.Handles (Semaphore)
import Vulkan.Core10.Handles (Semaphore(..))
import Vulkan.Core10.Enums.SharingMode (SharingMode)
import Vulkan.CStruct.Extends (SomeStruct)
import Vulkan.Core10.Enums.StructureType (StructureType)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_full_screen_exclusive (SurfaceFullScreenExclusiveInfoEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_full_screen_exclusive (SurfaceFullScreenExclusiveWin32InfoEXT)
import Vulkan.Extensions.Handles (SurfaceKHR)
import Vulkan.Extensions.Handles (SurfaceKHR(..))
import Vulkan.Extensions.VK_KHR_surface (SurfaceTransformFlagBitsKHR)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_display_control (SwapchainCounterCreateInfoEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_AMD_display_native_hdr (SwapchainDisplayNativeHdrCreateInfoAMD)
import Vulkan.Extensions.Handles (SwapchainKHR)
import Vulkan.Extensions.Handles (SwapchainKHR(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Exception (VulkanException(..))
import Vulkan.Zero (Zero)
import Vulkan.Zero (Zero(..))
import Vulkan.Core10.APIConstants (pattern MAX_DEVICE_GROUP_SIZE)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_ACQUIRE_NEXT_IMAGE_INFO_KHR))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_BIND_IMAGE_MEMORY_SWAPCHAIN_INFO_KHR))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_DEVICE_GROUP_PRESENT_CAPABILITIES_KHR))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_DEVICE_GROUP_PRESENT_INFO_KHR))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_DEVICE_GROUP_SWAPCHAIN_CREATE_INFO_KHR))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_IMAGE_SWAPCHAIN_CREATE_INFO_KHR))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PRESENT_INFO_KHR))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_SWAPCHAIN_CREATE_INFO_KHR))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
import Vulkan.Extensions.VK_KHR_surface (ColorSpaceKHR(..))
import Vulkan.Extensions.VK_KHR_surface (CompositeAlphaFlagBitsKHR(..))
import Vulkan.Extensions.VK_KHR_surface (CompositeAlphaFlagsKHR)
import Vulkan.Extensions.VK_KHR_surface (PresentModeKHR(..))
import Vulkan.Extensions.Handles (SurfaceKHR(..))
import Vulkan.Extensions.VK_KHR_surface (SurfaceTransformFlagBitsKHR(..))
import Vulkan.Extensions.VK_KHR_surface (SurfaceTransformFlagsKHR)
import Vulkan.Extensions.Handles (SwapchainKHR(..))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCreateSwapchainKHR
  :: FunPtr (Ptr Device_T -> Ptr (SomeStruct SwapchainCreateInfoKHR) -> Ptr AllocationCallbacks -> Ptr SwapchainKHR -> IO Result) -> Ptr Device_T -> Ptr (SomeStruct SwapchainCreateInfoKHR) -> Ptr AllocationCallbacks -> Ptr SwapchainKHR -> IO Result

-- | vkCreateSwapchainKHR - Create a swapchain
--
-- = Description
--
-- If the @oldSwapchain@ parameter of @pCreateInfo@ is a valid swapchain,
-- which has exclusive full-screen access, that access is released from
-- @oldSwapchain@. If the command succeeds in this case, the newly created
-- swapchain will automatically acquire exclusive full-screen access from
-- @oldSwapchain@.
--
-- Note
--
-- This implicit transfer is intended to avoid exiting and entering
-- full-screen exclusive mode, which may otherwise cause unwanted visual
-- updates to the display.
--
-- In some cases, swapchain creation /may/ fail if exclusive full-screen
-- mode is requested for application control, but for some
-- implementation-specific reason exclusive full-screen access is
-- unavailable for the particular combination of parameters provided. If
-- this occurs, 'Vulkan.Core10.Enums.Result.ERROR_INITIALIZATION_FAILED'
-- will be returned.
--
-- Note
--
-- In particular, it will fail if the @imageExtent@ member of @pCreateInfo@
-- does not match the extents of the monitor. Other reasons for failure may
-- include the app not being set as high-dpi aware, or if the physical
-- device and monitor are not compatible in this mode.
--
-- == Valid Usage (Implicit)
--
-- -   @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   @pCreateInfo@ /must/ be a valid pointer to a valid
--     'SwapchainCreateInfoKHR' structure
--
-- -   If @pAllocator@ is not @NULL@, @pAllocator@ /must/ be a valid
--     pointer to a valid
--     'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' structure
--
-- -   @pSwapchain@ /must/ be a valid pointer to a
--     'Vulkan.Extensions.Handles.SwapchainKHR' handle
--
-- == Host Synchronization
--
-- -   Host access to @pCreateInfo->surface@ /must/ be externally
--     synchronized
--
-- -   Host access to @pCreateInfo->oldSwapchain@ /must/ be externally
--     synchronized
--
-- == 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'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_DEVICE_LOST'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_SURFACE_LOST_KHR'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_NATIVE_WINDOW_IN_USE_KHR'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_INITIALIZATION_FAILED'
--
-- = See Also
--
-- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks',
-- 'Vulkan.Core10.Handles.Device', 'SwapchainCreateInfoKHR',
-- 'Vulkan.Extensions.Handles.SwapchainKHR'
createSwapchainKHR :: forall a io
                    . (Extendss SwapchainCreateInfoKHR a, PokeChain a, MonadIO io)
                   => -- | @device@ is the device to create the swapchain for.
                      Device
                   -> -- | @pCreateInfo@ is a pointer to a 'SwapchainCreateInfoKHR' structure
                      -- specifying the parameters of the created swapchain.
                      (SwapchainCreateInfoKHR a)
                   -> -- | @pAllocator@ is the allocator used for host memory allocated for the
                      -- swapchain 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 (SwapchainKHR)
createSwapchainKHR :: Device
-> SwapchainCreateInfoKHR a
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io SwapchainKHR
createSwapchainKHR device :: Device
device createInfo :: SwapchainCreateInfoKHR a
createInfo allocator :: "allocator" ::: Maybe AllocationCallbacks
allocator = IO SwapchainKHR -> io SwapchainKHR
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SwapchainKHR -> io SwapchainKHR)
-> (ContT SwapchainKHR IO SwapchainKHR -> IO SwapchainKHR)
-> ContT SwapchainKHR IO SwapchainKHR
-> io SwapchainKHR
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT SwapchainKHR IO SwapchainKHR -> IO SwapchainKHR
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT SwapchainKHR IO SwapchainKHR -> io SwapchainKHR)
-> ContT SwapchainKHR IO SwapchainKHR -> io SwapchainKHR
forall a b. (a -> b) -> a -> b
$ do
  let vkCreateSwapchainKHRPtr :: FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr (SomeStruct SwapchainCreateInfoKHR))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pSwapchain" ::: Ptr SwapchainKHR)
   -> IO Result)
vkCreateSwapchainKHRPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> ("pCreateInfo" ::: Ptr (SomeStruct SwapchainCreateInfoKHR))
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> ("pSwapchain" ::: Ptr SwapchainKHR)
      -> IO Result)
pVkCreateSwapchainKHR (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  IO () -> ContT SwapchainKHR IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT SwapchainKHR IO ())
-> IO () -> ContT SwapchainKHR IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr (SomeStruct SwapchainCreateInfoKHR))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pSwapchain" ::: Ptr SwapchainKHR)
   -> IO Result)
vkCreateSwapchainKHRPtr FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr (SomeStruct SwapchainCreateInfoKHR))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pSwapchain" ::: Ptr SwapchainKHR)
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> ("pCreateInfo" ::: Ptr (SomeStruct SwapchainCreateInfoKHR))
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> ("pSwapchain" ::: Ptr SwapchainKHR)
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr (SomeStruct SwapchainCreateInfoKHR))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pSwapchain" ::: Ptr SwapchainKHR)
   -> 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 "" "The function pointer for vkCreateSwapchainKHR is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCreateSwapchainKHR' :: Ptr Device_T
-> ("pCreateInfo" ::: Ptr (SomeStruct SwapchainCreateInfoKHR))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pSwapchain" ::: Ptr SwapchainKHR)
-> IO Result
vkCreateSwapchainKHR' = FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr (SomeStruct SwapchainCreateInfoKHR))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pSwapchain" ::: Ptr SwapchainKHR)
   -> IO Result)
-> Ptr Device_T
-> ("pCreateInfo" ::: Ptr (SomeStruct SwapchainCreateInfoKHR))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pSwapchain" ::: Ptr SwapchainKHR)
-> IO Result
mkVkCreateSwapchainKHR FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr (SomeStruct SwapchainCreateInfoKHR))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pSwapchain" ::: Ptr SwapchainKHR)
   -> IO Result)
vkCreateSwapchainKHRPtr
  Ptr (SwapchainCreateInfoKHR a)
pCreateInfo <- ((Ptr (SwapchainCreateInfoKHR a) -> IO SwapchainKHR)
 -> IO SwapchainKHR)
-> ContT SwapchainKHR IO (Ptr (SwapchainCreateInfoKHR a))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (SwapchainCreateInfoKHR a) -> IO SwapchainKHR)
  -> IO SwapchainKHR)
 -> ContT SwapchainKHR IO (Ptr (SwapchainCreateInfoKHR a)))
-> ((Ptr (SwapchainCreateInfoKHR a) -> IO SwapchainKHR)
    -> IO SwapchainKHR)
-> ContT SwapchainKHR IO (Ptr (SwapchainCreateInfoKHR a))
forall a b. (a -> b) -> a -> b
$ SwapchainCreateInfoKHR a
-> (Ptr (SwapchainCreateInfoKHR a) -> IO SwapchainKHR)
-> IO SwapchainKHR
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (SwapchainCreateInfoKHR a
createInfo)
  "pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
    Nothing -> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ContT SwapchainKHR IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall (f :: * -> *) a. Applicative f => a -> f a
pure "pAllocator" ::: Ptr AllocationCallbacks
forall a. Ptr a
nullPtr
    Just j :: AllocationCallbacks
j -> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO SwapchainKHR)
 -> IO SwapchainKHR)
-> ContT SwapchainKHR 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 SwapchainKHR)
  -> IO SwapchainKHR)
 -> ContT
      SwapchainKHR IO ("pAllocator" ::: Ptr AllocationCallbacks))
-> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO SwapchainKHR)
    -> IO SwapchainKHR)
-> ContT SwapchainKHR IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall a b. (a -> b) -> a -> b
$ AllocationCallbacks
-> (("pAllocator" ::: Ptr AllocationCallbacks) -> IO SwapchainKHR)
-> IO SwapchainKHR
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
  "pSwapchain" ::: Ptr SwapchainKHR
pPSwapchain <- ((("pSwapchain" ::: Ptr SwapchainKHR) -> IO SwapchainKHR)
 -> IO SwapchainKHR)
-> ContT SwapchainKHR IO ("pSwapchain" ::: Ptr SwapchainKHR)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pSwapchain" ::: Ptr SwapchainKHR) -> IO SwapchainKHR)
  -> IO SwapchainKHR)
 -> ContT SwapchainKHR IO ("pSwapchain" ::: Ptr SwapchainKHR))
-> ((("pSwapchain" ::: Ptr SwapchainKHR) -> IO SwapchainKHR)
    -> IO SwapchainKHR)
-> ContT SwapchainKHR IO ("pSwapchain" ::: Ptr SwapchainKHR)
forall a b. (a -> b) -> a -> b
$ IO ("pSwapchain" ::: Ptr SwapchainKHR)
-> (("pSwapchain" ::: Ptr SwapchainKHR) -> IO ())
-> (("pSwapchain" ::: Ptr SwapchainKHR) -> IO SwapchainKHR)
-> IO SwapchainKHR
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pSwapchain" ::: Ptr SwapchainKHR)
forall a. Int -> IO (Ptr a)
callocBytes @SwapchainKHR 8) ("pSwapchain" ::: Ptr SwapchainKHR) -> IO ()
forall a. Ptr a -> IO ()
free
  Result
r <- IO Result -> ContT SwapchainKHR IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT SwapchainKHR IO Result)
-> IO Result -> ContT SwapchainKHR IO Result
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> ("pCreateInfo" ::: Ptr (SomeStruct SwapchainCreateInfoKHR))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pSwapchain" ::: Ptr SwapchainKHR)
-> IO Result
vkCreateSwapchainKHR' (Device -> Ptr Device_T
deviceHandle (Device
device)) (Ptr (SwapchainCreateInfoKHR a)
-> "pCreateInfo" ::: Ptr (SomeStruct SwapchainCreateInfoKHR)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions Ptr (SwapchainCreateInfoKHR a)
pCreateInfo) "pAllocator" ::: Ptr AllocationCallbacks
pAllocator ("pSwapchain" ::: Ptr SwapchainKHR
pPSwapchain)
  IO () -> ContT SwapchainKHR IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT SwapchainKHR IO ())
-> IO () -> ContT SwapchainKHR 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))
  SwapchainKHR
pSwapchain <- IO SwapchainKHR -> ContT SwapchainKHR IO SwapchainKHR
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO SwapchainKHR -> ContT SwapchainKHR IO SwapchainKHR)
-> IO SwapchainKHR -> ContT SwapchainKHR IO SwapchainKHR
forall a b. (a -> b) -> a -> b
$ ("pSwapchain" ::: Ptr SwapchainKHR) -> IO SwapchainKHR
forall a. Storable a => Ptr a -> IO a
peek @SwapchainKHR "pSwapchain" ::: Ptr SwapchainKHR
pPSwapchain
  SwapchainKHR -> ContT SwapchainKHR IO SwapchainKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SwapchainKHR -> ContT SwapchainKHR IO SwapchainKHR)
-> SwapchainKHR -> ContT SwapchainKHR IO SwapchainKHR
forall a b. (a -> b) -> a -> b
$ (SwapchainKHR
pSwapchain)

-- | A convenience wrapper to make a compatible pair of calls to
-- 'createSwapchainKHR' and 'destroySwapchainKHR'
--
-- To ensure that 'destroySwapchainKHR' is always called: pass
-- 'Control.Exception.bracket' (or the allocate function from your
-- favourite resource management library) as the first argument.
-- To just extract the pair pass '(,)' as the first argument.
--
withSwapchainKHR :: forall a io r . (Extendss SwapchainCreateInfoKHR a, PokeChain a, MonadIO io) => Device -> SwapchainCreateInfoKHR a -> Maybe AllocationCallbacks -> (io (SwapchainKHR) -> ((SwapchainKHR) -> io ()) -> r) -> r
withSwapchainKHR :: Device
-> SwapchainCreateInfoKHR a
-> ("allocator" ::: Maybe AllocationCallbacks)
-> (io SwapchainKHR -> (SwapchainKHR -> io ()) -> r)
-> r
withSwapchainKHR device :: Device
device pCreateInfo :: SwapchainCreateInfoKHR a
pCreateInfo pAllocator :: "allocator" ::: Maybe AllocationCallbacks
pAllocator b :: io SwapchainKHR -> (SwapchainKHR -> io ()) -> r
b =
  io SwapchainKHR -> (SwapchainKHR -> io ()) -> r
b (Device
-> SwapchainCreateInfoKHR a
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io SwapchainKHR
forall (a :: [*]) (io :: * -> *).
(Extendss SwapchainCreateInfoKHR a, PokeChain a, MonadIO io) =>
Device
-> SwapchainCreateInfoKHR a
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io SwapchainKHR
createSwapchainKHR Device
device SwapchainCreateInfoKHR a
pCreateInfo "allocator" ::: Maybe AllocationCallbacks
pAllocator)
    (\(SwapchainKHR
o0) -> Device
-> SwapchainKHR
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ()
forall (io :: * -> *).
MonadIO io =>
Device
-> SwapchainKHR
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ()
destroySwapchainKHR Device
device SwapchainKHR
o0 "allocator" ::: Maybe AllocationCallbacks
pAllocator)


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkDestroySwapchainKHR
  :: FunPtr (Ptr Device_T -> SwapchainKHR -> Ptr AllocationCallbacks -> IO ()) -> Ptr Device_T -> SwapchainKHR -> Ptr AllocationCallbacks -> IO ()

-- | vkDestroySwapchainKHR - Destroy a swapchain object
--
-- = Description
--
-- The application /must/ not destroy a swapchain until after completion of
-- all outstanding operations on images that were acquired from the
-- swapchain. @swapchain@ and all associated 'Vulkan.Core10.Handles.Image'
-- handles are destroyed, and /must/ not be acquired or used any more by
-- the application. The memory of each 'Vulkan.Core10.Handles.Image' will
-- only be freed after that image is no longer used by the presentation
-- engine. For example, if one image of the swapchain is being displayed in
-- a window, the memory for that image /may/ not be freed until the window
-- is destroyed, or another swapchain is created for the window. Destroying
-- the swapchain does not invalidate the parent
-- 'Vulkan.Extensions.Handles.SurfaceKHR', and a new swapchain /can/ be
-- created with it.
--
-- When a swapchain associated with a display surface is destroyed, if the
-- image most recently presented to the display surface is from the
-- swapchain being destroyed, then either any display resources modified by
-- presenting images from any swapchain associated with the display surface
-- /must/ be reverted by the implementation to their state prior to the
-- first present performed on one of these swapchains, or such resources
-- /must/ be left in their current state.
--
-- If @swapchain@ has exclusive full-screen access, it is released before
-- the swapchain is destroyed.
--
-- == Valid Usage
--
-- -   All uses of presentable images acquired from @swapchain@ /must/ have
--     completed execution
--
-- -   If 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' were
--     provided when @swapchain@ was created, a compatible set of callbacks
--     /must/ be provided here
--
-- -   If no 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' were
--     provided when @swapchain@ was created, @pAllocator@ /must/ be @NULL@
--
-- == Valid Usage (Implicit)
--
-- -   @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   If @swapchain@ is not 'Vulkan.Core10.APIConstants.NULL_HANDLE',
--     @swapchain@ /must/ be a valid
--     'Vulkan.Extensions.Handles.SwapchainKHR' handle
--
-- -   If @pAllocator@ is not @NULL@, @pAllocator@ /must/ be a valid
--     pointer to a valid
--     'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' structure
--
-- -   Both of @device@, and @swapchain@ that are valid handles of
--     non-ignored parameters /must/ have been created, allocated, or
--     retrieved from the same 'Vulkan.Core10.Handles.Instance'
--
-- == Host Synchronization
--
-- -   Host access to @swapchain@ /must/ be externally synchronized
--
-- = See Also
--
-- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks',
-- 'Vulkan.Core10.Handles.Device', 'Vulkan.Extensions.Handles.SwapchainKHR'
destroySwapchainKHR :: forall io
                     . (MonadIO io)
                    => -- | @device@ is the 'Vulkan.Core10.Handles.Device' associated with
                       -- @swapchain@.
                       Device
                    -> -- | @swapchain@ is the swapchain to destroy.
                       SwapchainKHR
                    -> -- | @pAllocator@ is the allocator used for host memory allocated for the
                       -- swapchain 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 ()
destroySwapchainKHR :: Device
-> SwapchainKHR
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ()
destroySwapchainKHR device :: Device
device swapchain :: SwapchainKHR
swapchain allocator :: "allocator" ::: Maybe AllocationCallbacks
allocator = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (ContT () IO () -> IO ()) -> ContT () IO () -> io ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT () IO () -> IO ()
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkDestroySwapchainKHRPtr :: FunPtr
  (Ptr Device_T
   -> SwapchainKHR
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
vkDestroySwapchainKHRPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> SwapchainKHR
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> IO ())
pVkDestroySwapchainKHR (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> SwapchainKHR
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
vkDestroySwapchainKHRPtr FunPtr
  (Ptr Device_T
   -> SwapchainKHR
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
-> FunPtr
     (Ptr Device_T
      -> SwapchainKHR
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> SwapchainKHR
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
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 "" "The function pointer for vkDestroySwapchainKHR is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkDestroySwapchainKHR' :: Ptr Device_T
-> SwapchainKHR
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ()
vkDestroySwapchainKHR' = FunPtr
  (Ptr Device_T
   -> SwapchainKHR
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
-> Ptr Device_T
-> SwapchainKHR
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ()
mkVkDestroySwapchainKHR FunPtr
  (Ptr Device_T
   -> SwapchainKHR
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
vkDestroySwapchainKHRPtr
  "pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
    Nothing -> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall (f :: * -> *) a. Applicative f => a -> f a
pure "pAllocator" ::: Ptr AllocationCallbacks
forall a. Ptr a
nullPtr
    Just j :: AllocationCallbacks
j -> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ())
-> ContT () 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 ()) -> IO ())
 -> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks))
-> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ())
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall a b. (a -> b) -> a -> b
$ AllocationCallbacks
-> (("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> SwapchainKHR
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ()
vkDestroySwapchainKHR' (Device -> Ptr Device_T
deviceHandle (Device
device)) (SwapchainKHR
swapchain) "pAllocator" ::: Ptr AllocationCallbacks
pAllocator
  () -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkGetSwapchainImagesKHR
  :: FunPtr (Ptr Device_T -> SwapchainKHR -> Ptr Word32 -> Ptr Image -> IO Result) -> Ptr Device_T -> SwapchainKHR -> Ptr Word32 -> Ptr Image -> IO Result

-- | vkGetSwapchainImagesKHR - Obtain the array of presentable images
-- associated with a swapchain
--
-- = Description
--
-- If @pSwapchainImages@ is @NULL@, then the number of presentable images
-- for @swapchain@ is returned in @pSwapchainImageCount@. Otherwise,
-- @pSwapchainImageCount@ /must/ point to a variable set by the user to the
-- number of elements in the @pSwapchainImages@ array, and on return the
-- variable is overwritten with the number of structures actually written
-- to @pSwapchainImages@. If the value of @pSwapchainImageCount@ is less
-- than the number of presentable images for @swapchain@, at most
-- @pSwapchainImageCount@ structures will be written. If
-- @pSwapchainImageCount@ is smaller than the number of presentable images
-- for @swapchain@, 'Vulkan.Core10.Enums.Result.INCOMPLETE' will be
-- returned instead of 'Vulkan.Core10.Enums.Result.SUCCESS' to indicate
-- that not all the available values were returned.
--
-- == Valid Usage (Implicit)
--
-- -   @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   @swapchain@ /must/ be a valid
--     'Vulkan.Extensions.Handles.SwapchainKHR' handle
--
-- -   @pSwapchainImageCount@ /must/ be a valid pointer to a @uint32_t@
--     value
--
-- -   If the value referenced by @pSwapchainImageCount@ is not @0@, and
--     @pSwapchainImages@ is not @NULL@, @pSwapchainImages@ /must/ be a
--     valid pointer to an array of @pSwapchainImageCount@
--     'Vulkan.Core10.Handles.Image' handles
--
-- -   Both of @device@, and @swapchain@ /must/ have been created,
--     allocated, or retrieved from the same
--     'Vulkan.Core10.Handles.Instance'
--
-- == Return Codes
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>]
--
--     -   'Vulkan.Core10.Enums.Result.SUCCESS'
--
--     -   'Vulkan.Core10.Enums.Result.INCOMPLETE'
--
-- [<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
--
-- 'Vulkan.Core10.Handles.Device', 'Vulkan.Core10.Handles.Image',
-- 'Vulkan.Extensions.Handles.SwapchainKHR'
getSwapchainImagesKHR :: forall io
                       . (MonadIO io)
                      => -- | @device@ is the device associated with @swapchain@.
                         Device
                      -> -- | @swapchain@ is the swapchain to query.
                         SwapchainKHR
                      -> io (Result, ("swapchainImages" ::: Vector Image))
getSwapchainImagesKHR :: Device
-> SwapchainKHR -> io (Result, "swapchainImages" ::: Vector Image)
getSwapchainImagesKHR device :: Device
device swapchain :: SwapchainKHR
swapchain = IO (Result, "swapchainImages" ::: Vector Image)
-> io (Result, "swapchainImages" ::: Vector Image)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Result, "swapchainImages" ::: Vector Image)
 -> io (Result, "swapchainImages" ::: Vector Image))
-> (ContT
      (Result, "swapchainImages" ::: Vector Image)
      IO
      (Result, "swapchainImages" ::: Vector Image)
    -> IO (Result, "swapchainImages" ::: Vector Image))
-> ContT
     (Result, "swapchainImages" ::: Vector Image)
     IO
     (Result, "swapchainImages" ::: Vector Image)
-> io (Result, "swapchainImages" ::: Vector Image)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT
  (Result, "swapchainImages" ::: Vector Image)
  IO
  (Result, "swapchainImages" ::: Vector Image)
-> IO (Result, "swapchainImages" ::: Vector Image)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT
   (Result, "swapchainImages" ::: Vector Image)
   IO
   (Result, "swapchainImages" ::: Vector Image)
 -> io (Result, "swapchainImages" ::: Vector Image))
-> ContT
     (Result, "swapchainImages" ::: Vector Image)
     IO
     (Result, "swapchainImages" ::: Vector Image)
-> io (Result, "swapchainImages" ::: Vector Image)
forall a b. (a -> b) -> a -> b
$ do
  let vkGetSwapchainImagesKHRPtr :: FunPtr
  (Ptr Device_T
   -> SwapchainKHR
   -> ("pSwapchainImageCount" ::: Ptr Word32)
   -> ("pSwapchainImages" ::: Ptr Image)
   -> IO Result)
vkGetSwapchainImagesKHRPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> SwapchainKHR
      -> ("pSwapchainImageCount" ::: Ptr Word32)
      -> ("pSwapchainImages" ::: Ptr Image)
      -> IO Result)
pVkGetSwapchainImagesKHR (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  IO () -> ContT (Result, "swapchainImages" ::: Vector Image) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (Result, "swapchainImages" ::: Vector Image) IO ())
-> IO ()
-> ContT (Result, "swapchainImages" ::: Vector Image) IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> SwapchainKHR
   -> ("pSwapchainImageCount" ::: Ptr Word32)
   -> ("pSwapchainImages" ::: Ptr Image)
   -> IO Result)
vkGetSwapchainImagesKHRPtr FunPtr
  (Ptr Device_T
   -> SwapchainKHR
   -> ("pSwapchainImageCount" ::: Ptr Word32)
   -> ("pSwapchainImages" ::: Ptr Image)
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> SwapchainKHR
      -> ("pSwapchainImageCount" ::: Ptr Word32)
      -> ("pSwapchainImages" ::: Ptr Image)
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> SwapchainKHR
   -> ("pSwapchainImageCount" ::: Ptr Word32)
   -> ("pSwapchainImages" ::: Ptr Image)
   -> 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 "" "The function pointer for vkGetSwapchainImagesKHR is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetSwapchainImagesKHR' :: Ptr Device_T
-> SwapchainKHR
-> ("pSwapchainImageCount" ::: Ptr Word32)
-> ("pSwapchainImages" ::: Ptr Image)
-> IO Result
vkGetSwapchainImagesKHR' = FunPtr
  (Ptr Device_T
   -> SwapchainKHR
   -> ("pSwapchainImageCount" ::: Ptr Word32)
   -> ("pSwapchainImages" ::: Ptr Image)
   -> IO Result)
-> Ptr Device_T
-> SwapchainKHR
-> ("pSwapchainImageCount" ::: Ptr Word32)
-> ("pSwapchainImages" ::: Ptr Image)
-> IO Result
mkVkGetSwapchainImagesKHR FunPtr
  (Ptr Device_T
   -> SwapchainKHR
   -> ("pSwapchainImageCount" ::: Ptr Word32)
   -> ("pSwapchainImages" ::: Ptr Image)
   -> IO Result)
vkGetSwapchainImagesKHRPtr
  let device' :: Ptr Device_T
device' = Device -> Ptr Device_T
deviceHandle (Device
device)
  "pSwapchainImageCount" ::: Ptr Word32
pPSwapchainImageCount <- ((("pSwapchainImageCount" ::: Ptr Word32)
  -> IO (Result, "swapchainImages" ::: Vector Image))
 -> IO (Result, "swapchainImages" ::: Vector Image))
-> ContT
     (Result, "swapchainImages" ::: Vector Image)
     IO
     ("pSwapchainImageCount" ::: Ptr Word32)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pSwapchainImageCount" ::: Ptr Word32)
   -> IO (Result, "swapchainImages" ::: Vector Image))
  -> IO (Result, "swapchainImages" ::: Vector Image))
 -> ContT
      (Result, "swapchainImages" ::: Vector Image)
      IO
      ("pSwapchainImageCount" ::: Ptr Word32))
-> ((("pSwapchainImageCount" ::: Ptr Word32)
     -> IO (Result, "swapchainImages" ::: Vector Image))
    -> IO (Result, "swapchainImages" ::: Vector Image))
-> ContT
     (Result, "swapchainImages" ::: Vector Image)
     IO
     ("pSwapchainImageCount" ::: Ptr Word32)
forall a b. (a -> b) -> a -> b
$ IO ("pSwapchainImageCount" ::: Ptr Word32)
-> (("pSwapchainImageCount" ::: Ptr Word32) -> IO ())
-> (("pSwapchainImageCount" ::: Ptr Word32)
    -> IO (Result, "swapchainImages" ::: Vector Image))
-> IO (Result, "swapchainImages" ::: Vector Image)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pSwapchainImageCount" ::: Ptr Word32)
forall a. Int -> IO (Ptr a)
callocBytes @Word32 4) ("pSwapchainImageCount" ::: Ptr Word32) -> IO ()
forall a. Ptr a -> IO ()
free
  Result
r <- IO Result
-> ContT (Result, "swapchainImages" ::: Vector Image) IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result
 -> ContT (Result, "swapchainImages" ::: Vector Image) IO Result)
-> IO Result
-> ContT (Result, "swapchainImages" ::: Vector Image) IO Result
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> SwapchainKHR
-> ("pSwapchainImageCount" ::: Ptr Word32)
-> ("pSwapchainImages" ::: Ptr Image)
-> IO Result
vkGetSwapchainImagesKHR' Ptr Device_T
device' (SwapchainKHR
swapchain) ("pSwapchainImageCount" ::: Ptr Word32
pPSwapchainImageCount) ("pSwapchainImages" ::: Ptr Image
forall a. Ptr a
nullPtr)
  IO () -> ContT (Result, "swapchainImages" ::: Vector Image) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (Result, "swapchainImages" ::: Vector Image) IO ())
-> IO ()
-> ContT (Result, "swapchainImages" ::: Vector Image) 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))
  Word32
pSwapchainImageCount <- IO Word32
-> ContT (Result, "swapchainImages" ::: Vector Image) IO Word32
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Word32
 -> ContT (Result, "swapchainImages" ::: Vector Image) IO Word32)
-> IO Word32
-> ContT (Result, "swapchainImages" ::: Vector Image) IO Word32
forall a b. (a -> b) -> a -> b
$ ("pSwapchainImageCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 "pSwapchainImageCount" ::: Ptr Word32
pPSwapchainImageCount
  "pSwapchainImages" ::: Ptr Image
pPSwapchainImages <- ((("pSwapchainImages" ::: Ptr Image)
  -> IO (Result, "swapchainImages" ::: Vector Image))
 -> IO (Result, "swapchainImages" ::: Vector Image))
-> ContT
     (Result, "swapchainImages" ::: Vector Image)
     IO
     ("pSwapchainImages" ::: Ptr Image)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pSwapchainImages" ::: Ptr Image)
   -> IO (Result, "swapchainImages" ::: Vector Image))
  -> IO (Result, "swapchainImages" ::: Vector Image))
 -> ContT
      (Result, "swapchainImages" ::: Vector Image)
      IO
      ("pSwapchainImages" ::: Ptr Image))
-> ((("pSwapchainImages" ::: Ptr Image)
     -> IO (Result, "swapchainImages" ::: Vector Image))
    -> IO (Result, "swapchainImages" ::: Vector Image))
-> ContT
     (Result, "swapchainImages" ::: Vector Image)
     IO
     ("pSwapchainImages" ::: Ptr Image)
forall a b. (a -> b) -> a -> b
$ IO ("pSwapchainImages" ::: Ptr Image)
-> (("pSwapchainImages" ::: Ptr Image) -> IO ())
-> (("pSwapchainImages" ::: Ptr Image)
    -> IO (Result, "swapchainImages" ::: Vector Image))
-> IO (Result, "swapchainImages" ::: Vector Image)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pSwapchainImages" ::: Ptr Image)
forall a. Int -> IO (Ptr a)
callocBytes @Image ((Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pSwapchainImageCount)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8)) ("pSwapchainImages" ::: Ptr Image) -> IO ()
forall a. Ptr a -> IO ()
free
  Result
r' <- IO Result
-> ContT (Result, "swapchainImages" ::: Vector Image) IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result
 -> ContT (Result, "swapchainImages" ::: Vector Image) IO Result)
-> IO Result
-> ContT (Result, "swapchainImages" ::: Vector Image) IO Result
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> SwapchainKHR
-> ("pSwapchainImageCount" ::: Ptr Word32)
-> ("pSwapchainImages" ::: Ptr Image)
-> IO Result
vkGetSwapchainImagesKHR' Ptr Device_T
device' (SwapchainKHR
swapchain) ("pSwapchainImageCount" ::: Ptr Word32
pPSwapchainImageCount) ("pSwapchainImages" ::: Ptr Image
pPSwapchainImages)
  IO () -> ContT (Result, "swapchainImages" ::: Vector Image) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (Result, "swapchainImages" ::: Vector Image) IO ())
-> IO ()
-> ContT (Result, "swapchainImages" ::: Vector Image) 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'))
  Word32
pSwapchainImageCount' <- IO Word32
-> ContT (Result, "swapchainImages" ::: Vector Image) IO Word32
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Word32
 -> ContT (Result, "swapchainImages" ::: Vector Image) IO Word32)
-> IO Word32
-> ContT (Result, "swapchainImages" ::: Vector Image) IO Word32
forall a b. (a -> b) -> a -> b
$ ("pSwapchainImageCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 "pSwapchainImageCount" ::: Ptr Word32
pPSwapchainImageCount
  "swapchainImages" ::: Vector Image
pSwapchainImages' <- IO ("swapchainImages" ::: Vector Image)
-> ContT
     (Result, "swapchainImages" ::: Vector Image)
     IO
     ("swapchainImages" ::: Vector Image)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ("swapchainImages" ::: Vector Image)
 -> ContT
      (Result, "swapchainImages" ::: Vector Image)
      IO
      ("swapchainImages" ::: Vector Image))
-> IO ("swapchainImages" ::: Vector Image)
-> ContT
     (Result, "swapchainImages" ::: Vector Image)
     IO
     ("swapchainImages" ::: Vector Image)
forall a b. (a -> b) -> a -> b
$ Int -> (Int -> IO Image) -> IO ("swapchainImages" ::: Vector Image)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pSwapchainImageCount')) (\i :: Int
i -> ("pSwapchainImages" ::: Ptr Image) -> IO Image
forall a. Storable a => Ptr a -> IO a
peek @Image (("pSwapchainImages" ::: Ptr Image
pPSwapchainImages ("pSwapchainImages" ::: Ptr Image)
-> Int -> "pSwapchainImages" ::: Ptr Image
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Image)))
  (Result, "swapchainImages" ::: Vector Image)
-> ContT
     (Result, "swapchainImages" ::: Vector Image)
     IO
     (Result, "swapchainImages" ::: Vector Image)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Result, "swapchainImages" ::: Vector Image)
 -> ContT
      (Result, "swapchainImages" ::: Vector Image)
      IO
      (Result, "swapchainImages" ::: Vector Image))
-> (Result, "swapchainImages" ::: Vector Image)
-> ContT
     (Result, "swapchainImages" ::: Vector Image)
     IO
     (Result, "swapchainImages" ::: Vector Image)
forall a b. (a -> b) -> a -> b
$ ((Result
r'), "swapchainImages" ::: Vector Image
pSwapchainImages')


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkAcquireNextImageKHRUnsafe
  :: FunPtr (Ptr Device_T -> SwapchainKHR -> Word64 -> Semaphore -> Fence -> Ptr Word32 -> IO Result) -> Ptr Device_T -> SwapchainKHR -> Word64 -> Semaphore -> Fence -> Ptr Word32 -> IO Result

foreign import ccall
  "dynamic" mkVkAcquireNextImageKHRSafe
  :: FunPtr (Ptr Device_T -> SwapchainKHR -> Word64 -> Semaphore -> Fence -> Ptr Word32 -> IO Result) -> Ptr Device_T -> SwapchainKHR -> Word64 -> Semaphore -> Fence -> Ptr Word32 -> IO Result

-- | acquireNextImageKHR with selectable safeness
acquireNextImageKHRSafeOrUnsafe :: forall io
                                 . (MonadIO io)
                                => -- No documentation found for TopLevel ""
                                   (FunPtr (Ptr Device_T -> SwapchainKHR -> Word64 -> Semaphore -> Fence -> Ptr Word32 -> IO Result) -> Ptr Device_T -> SwapchainKHR -> Word64 -> Semaphore -> Fence -> Ptr Word32 -> IO Result)
                                -> -- | @device@ is the device associated with @swapchain@.
                                   Device
                                -> -- | @swapchain@ is the non-retired swapchain from which an image is being
                                   -- acquired.
                                   SwapchainKHR
                                -> -- | @timeout@ specifies how long the function waits, in nanoseconds, if no
                                   -- image is available.
                                   ("timeout" ::: Word64)
                                -> -- | @semaphore@ is 'Vulkan.Core10.APIConstants.NULL_HANDLE' or a semaphore
                                   -- to signal.
                                   Semaphore
                                -> -- | @fence@ is 'Vulkan.Core10.APIConstants.NULL_HANDLE' or a fence to
                                   -- signal.
                                   Fence
                                -> io (Result, ("imageIndex" ::: Word32))
acquireNextImageKHRSafeOrUnsafe :: (FunPtr
   (Ptr Device_T
    -> SwapchainKHR
    -> Word64
    -> Semaphore
    -> Fence
    -> ("pSwapchainImageCount" ::: Ptr Word32)
    -> IO Result)
 -> Ptr Device_T
 -> SwapchainKHR
 -> Word64
 -> Semaphore
 -> Fence
 -> ("pSwapchainImageCount" ::: Ptr Word32)
 -> IO Result)
-> Device
-> SwapchainKHR
-> Word64
-> Semaphore
-> Fence
-> io (Result, Word32)
acquireNextImageKHRSafeOrUnsafe mkVkAcquireNextImageKHR :: FunPtr
  (Ptr Device_T
   -> SwapchainKHR
   -> Word64
   -> Semaphore
   -> Fence
   -> ("pSwapchainImageCount" ::: Ptr Word32)
   -> IO Result)
-> Ptr Device_T
-> SwapchainKHR
-> Word64
-> Semaphore
-> Fence
-> ("pSwapchainImageCount" ::: Ptr Word32)
-> IO Result
mkVkAcquireNextImageKHR device :: Device
device swapchain :: SwapchainKHR
swapchain timeout :: Word64
timeout semaphore :: Semaphore
semaphore fence :: Fence
fence = IO (Result, Word32) -> io (Result, Word32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Result, Word32) -> io (Result, Word32))
-> (ContT (Result, Word32) IO (Result, Word32)
    -> IO (Result, Word32))
-> ContT (Result, Word32) IO (Result, Word32)
-> io (Result, Word32)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT (Result, Word32) IO (Result, Word32) -> IO (Result, Word32)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT (Result, Word32) IO (Result, Word32) -> io (Result, Word32))
-> ContT (Result, Word32) IO (Result, Word32)
-> io (Result, Word32)
forall a b. (a -> b) -> a -> b
$ do
  let vkAcquireNextImageKHRPtr :: FunPtr
  (Ptr Device_T
   -> SwapchainKHR
   -> Word64
   -> Semaphore
   -> Fence
   -> ("pSwapchainImageCount" ::: Ptr Word32)
   -> IO Result)
vkAcquireNextImageKHRPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> SwapchainKHR
      -> Word64
      -> Semaphore
      -> Fence
      -> ("pSwapchainImageCount" ::: Ptr Word32)
      -> IO Result)
pVkAcquireNextImageKHR (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  IO () -> ContT (Result, Word32) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (Result, Word32) IO ())
-> IO () -> ContT (Result, Word32) IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> SwapchainKHR
   -> Word64
   -> Semaphore
   -> Fence
   -> ("pSwapchainImageCount" ::: Ptr Word32)
   -> IO Result)
vkAcquireNextImageKHRPtr FunPtr
  (Ptr Device_T
   -> SwapchainKHR
   -> Word64
   -> Semaphore
   -> Fence
   -> ("pSwapchainImageCount" ::: Ptr Word32)
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> SwapchainKHR
      -> Word64
      -> Semaphore
      -> Fence
      -> ("pSwapchainImageCount" ::: Ptr Word32)
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> SwapchainKHR
   -> Word64
   -> Semaphore
   -> Fence
   -> ("pSwapchainImageCount" ::: Ptr Word32)
   -> 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 "" "The function pointer for vkAcquireNextImageKHR is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkAcquireNextImageKHR' :: Ptr Device_T
-> SwapchainKHR
-> Word64
-> Semaphore
-> Fence
-> ("pSwapchainImageCount" ::: Ptr Word32)
-> IO Result
vkAcquireNextImageKHR' = FunPtr
  (Ptr Device_T
   -> SwapchainKHR
   -> Word64
   -> Semaphore
   -> Fence
   -> ("pSwapchainImageCount" ::: Ptr Word32)
   -> IO Result)
-> Ptr Device_T
-> SwapchainKHR
-> Word64
-> Semaphore
-> Fence
-> ("pSwapchainImageCount" ::: Ptr Word32)
-> IO Result
mkVkAcquireNextImageKHR FunPtr
  (Ptr Device_T
   -> SwapchainKHR
   -> Word64
   -> Semaphore
   -> Fence
   -> ("pSwapchainImageCount" ::: Ptr Word32)
   -> IO Result)
vkAcquireNextImageKHRPtr
  "pSwapchainImageCount" ::: Ptr Word32
pPImageIndex <- ((("pSwapchainImageCount" ::: Ptr Word32) -> IO (Result, Word32))
 -> IO (Result, Word32))
-> ContT
     (Result, Word32) IO ("pSwapchainImageCount" ::: Ptr Word32)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pSwapchainImageCount" ::: Ptr Word32) -> IO (Result, Word32))
  -> IO (Result, Word32))
 -> ContT
      (Result, Word32) IO ("pSwapchainImageCount" ::: Ptr Word32))
-> ((("pSwapchainImageCount" ::: Ptr Word32)
     -> IO (Result, Word32))
    -> IO (Result, Word32))
-> ContT
     (Result, Word32) IO ("pSwapchainImageCount" ::: Ptr Word32)
forall a b. (a -> b) -> a -> b
$ IO ("pSwapchainImageCount" ::: Ptr Word32)
-> (("pSwapchainImageCount" ::: Ptr Word32) -> IO ())
-> (("pSwapchainImageCount" ::: Ptr Word32) -> IO (Result, Word32))
-> IO (Result, Word32)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pSwapchainImageCount" ::: Ptr Word32)
forall a. Int -> IO (Ptr a)
callocBytes @Word32 4) ("pSwapchainImageCount" ::: Ptr Word32) -> IO ()
forall a. Ptr a -> IO ()
free
  Result
r <- IO Result -> ContT (Result, Word32) IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT (Result, Word32) IO Result)
-> IO Result -> ContT (Result, Word32) IO Result
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> SwapchainKHR
-> Word64
-> Semaphore
-> Fence
-> ("pSwapchainImageCount" ::: Ptr Word32)
-> IO Result
vkAcquireNextImageKHR' (Device -> Ptr Device_T
deviceHandle (Device
device)) (SwapchainKHR
swapchain) (Word64
timeout) (Semaphore
semaphore) (Fence
fence) ("pSwapchainImageCount" ::: Ptr Word32
pPImageIndex)
  IO () -> ContT (Result, Word32) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (Result, Word32) IO ())
-> IO () -> ContT (Result, Word32) 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))
  Word32
pImageIndex <- IO Word32 -> ContT (Result, Word32) IO Word32
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Word32 -> ContT (Result, Word32) IO Word32)
-> IO Word32 -> ContT (Result, Word32) IO Word32
forall a b. (a -> b) -> a -> b
$ ("pSwapchainImageCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 "pSwapchainImageCount" ::: Ptr Word32
pPImageIndex
  (Result, Word32) -> ContT (Result, Word32) IO (Result, Word32)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Result, Word32) -> ContT (Result, Word32) IO (Result, Word32))
-> (Result, Word32) -> ContT (Result, Word32) IO (Result, Word32)
forall a b. (a -> b) -> a -> b
$ (Result
r, Word32
pImageIndex)

-- | vkAcquireNextImageKHR - Retrieve the index of the next available
-- presentable image
--
-- == Valid Usage
--
-- -   @swapchain@ /must/ not be in the retired state
--
-- -   If @semaphore@ is not 'Vulkan.Core10.APIConstants.NULL_HANDLE' it
--     /must/ be unsignaled
--
-- -   If @semaphore@ is not 'Vulkan.Core10.APIConstants.NULL_HANDLE' it
--     /must/ not have any uncompleted signal or wait operations pending
--
-- -   If @fence@ is not 'Vulkan.Core10.APIConstants.NULL_HANDLE' it /must/
--     be unsignaled and /must/ not be associated with any other queue
--     command that has not yet completed execution on that queue
--
-- -   @semaphore@ and @fence@ /must/ not both be equal to
--     'Vulkan.Core10.APIConstants.NULL_HANDLE'
--
-- -   If the number of currently acquired images is greater than the
--     difference between the number of images in @swapchain@ and the value
--     of
--     'Vulkan.Extensions.VK_KHR_surface.SurfaceCapabilitiesKHR'::@minImageCount@
--     as returned by a call to
--     'Vulkan.Extensions.VK_KHR_get_surface_capabilities2.getPhysicalDeviceSurfaceCapabilities2KHR'
--     with the @surface@ used to create @swapchain@, @timeout@ /must/ not
--     be @UINT64_MAX@
--
-- -   @semaphore@ /must/ have a
--     'Vulkan.Core12.Enums.SemaphoreType.SemaphoreType' of
--     'Vulkan.Core12.Enums.SemaphoreType.SEMAPHORE_TYPE_BINARY'
--
-- == Valid Usage (Implicit)
--
-- -   @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   @swapchain@ /must/ be a valid
--     'Vulkan.Extensions.Handles.SwapchainKHR' handle
--
-- -   If @semaphore@ is not 'Vulkan.Core10.APIConstants.NULL_HANDLE',
--     @semaphore@ /must/ be a valid 'Vulkan.Core10.Handles.Semaphore'
--     handle
--
-- -   If @fence@ is not 'Vulkan.Core10.APIConstants.NULL_HANDLE', @fence@
--     /must/ be a valid 'Vulkan.Core10.Handles.Fence' handle
--
-- -   @pImageIndex@ /must/ be a valid pointer to a @uint32_t@ value
--
-- -   If @semaphore@ is a valid handle, it /must/ have been created,
--     allocated, or retrieved from @device@
--
-- -   If @fence@ is a valid handle, it /must/ have been created,
--     allocated, or retrieved from @device@
--
-- -   Both of @device@, and @swapchain@ that are valid handles of
--     non-ignored parameters /must/ have been created, allocated, or
--     retrieved from the same 'Vulkan.Core10.Handles.Instance'
--
-- == Host Synchronization
--
-- -   Host access to @swapchain@ /must/ be externally synchronized
--
-- -   Host access to @semaphore@ /must/ be externally synchronized
--
-- -   Host access to @fence@ /must/ be externally synchronized
--
-- == Return Codes
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>]
--
--     -   'Vulkan.Core10.Enums.Result.SUCCESS'
--
--     -   'Vulkan.Core10.Enums.Result.TIMEOUT'
--
--     -   'Vulkan.Core10.Enums.Result.NOT_READY'
--
--     -   'Vulkan.Core10.Enums.Result.SUBOPTIMAL_KHR'
--
-- [<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'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_DEVICE_LOST'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_DATE_KHR'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_SURFACE_LOST_KHR'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_FULL_SCREEN_EXCLUSIVE_MODE_LOST_EXT'
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.Device', 'Vulkan.Core10.Handles.Fence',
-- 'Vulkan.Core10.Handles.Semaphore',
-- 'Vulkan.Extensions.Handles.SwapchainKHR'
acquireNextImageKHR :: forall io
                     . (MonadIO io)
                    => -- | @device@ is the device associated with @swapchain@.
                       Device
                    -> -- | @swapchain@ is the non-retired swapchain from which an image is being
                       -- acquired.
                       SwapchainKHR
                    -> -- | @timeout@ specifies how long the function waits, in nanoseconds, if no
                       -- image is available.
                       ("timeout" ::: Word64)
                    -> -- | @semaphore@ is 'Vulkan.Core10.APIConstants.NULL_HANDLE' or a semaphore
                       -- to signal.
                       Semaphore
                    -> -- | @fence@ is 'Vulkan.Core10.APIConstants.NULL_HANDLE' or a fence to
                       -- signal.
                       Fence
                    -> io (Result, ("imageIndex" ::: Word32))
acquireNextImageKHR :: Device
-> SwapchainKHR
-> Word64
-> Semaphore
-> Fence
-> io (Result, Word32)
acquireNextImageKHR = (FunPtr
   (Ptr Device_T
    -> SwapchainKHR
    -> Word64
    -> Semaphore
    -> Fence
    -> ("pSwapchainImageCount" ::: Ptr Word32)
    -> IO Result)
 -> Ptr Device_T
 -> SwapchainKHR
 -> Word64
 -> Semaphore
 -> Fence
 -> ("pSwapchainImageCount" ::: Ptr Word32)
 -> IO Result)
-> Device
-> SwapchainKHR
-> Word64
-> Semaphore
-> Fence
-> io (Result, Word32)
forall (io :: * -> *).
MonadIO io =>
(FunPtr
   (Ptr Device_T
    -> SwapchainKHR
    -> Word64
    -> Semaphore
    -> Fence
    -> ("pSwapchainImageCount" ::: Ptr Word32)
    -> IO Result)
 -> Ptr Device_T
 -> SwapchainKHR
 -> Word64
 -> Semaphore
 -> Fence
 -> ("pSwapchainImageCount" ::: Ptr Word32)
 -> IO Result)
-> Device
-> SwapchainKHR
-> Word64
-> Semaphore
-> Fence
-> io (Result, Word32)
acquireNextImageKHRSafeOrUnsafe FunPtr
  (Ptr Device_T
   -> SwapchainKHR
   -> Word64
   -> Semaphore
   -> Fence
   -> ("pSwapchainImageCount" ::: Ptr Word32)
   -> IO Result)
-> Ptr Device_T
-> SwapchainKHR
-> Word64
-> Semaphore
-> Fence
-> ("pSwapchainImageCount" ::: Ptr Word32)
-> IO Result
mkVkAcquireNextImageKHRUnsafe

-- | A variant of 'acquireNextImageKHR' which makes a *safe* FFI call
acquireNextImageKHRSafe :: forall io
                         . (MonadIO io)
                        => -- | @device@ is the device associated with @swapchain@.
                           Device
                        -> -- | @swapchain@ is the non-retired swapchain from which an image is being
                           -- acquired.
                           SwapchainKHR
                        -> -- | @timeout@ specifies how long the function waits, in nanoseconds, if no
                           -- image is available.
                           ("timeout" ::: Word64)
                        -> -- | @semaphore@ is 'Vulkan.Core10.APIConstants.NULL_HANDLE' or a semaphore
                           -- to signal.
                           Semaphore
                        -> -- | @fence@ is 'Vulkan.Core10.APIConstants.NULL_HANDLE' or a fence to
                           -- signal.
                           Fence
                        -> io (Result, ("imageIndex" ::: Word32))
acquireNextImageKHRSafe :: Device
-> SwapchainKHR
-> Word64
-> Semaphore
-> Fence
-> io (Result, Word32)
acquireNextImageKHRSafe = (FunPtr
   (Ptr Device_T
    -> SwapchainKHR
    -> Word64
    -> Semaphore
    -> Fence
    -> ("pSwapchainImageCount" ::: Ptr Word32)
    -> IO Result)
 -> Ptr Device_T
 -> SwapchainKHR
 -> Word64
 -> Semaphore
 -> Fence
 -> ("pSwapchainImageCount" ::: Ptr Word32)
 -> IO Result)
-> Device
-> SwapchainKHR
-> Word64
-> Semaphore
-> Fence
-> io (Result, Word32)
forall (io :: * -> *).
MonadIO io =>
(FunPtr
   (Ptr Device_T
    -> SwapchainKHR
    -> Word64
    -> Semaphore
    -> Fence
    -> ("pSwapchainImageCount" ::: Ptr Word32)
    -> IO Result)
 -> Ptr Device_T
 -> SwapchainKHR
 -> Word64
 -> Semaphore
 -> Fence
 -> ("pSwapchainImageCount" ::: Ptr Word32)
 -> IO Result)
-> Device
-> SwapchainKHR
-> Word64
-> Semaphore
-> Fence
-> io (Result, Word32)
acquireNextImageKHRSafeOrUnsafe FunPtr
  (Ptr Device_T
   -> SwapchainKHR
   -> Word64
   -> Semaphore
   -> Fence
   -> ("pSwapchainImageCount" ::: Ptr Word32)
   -> IO Result)
-> Ptr Device_T
-> SwapchainKHR
-> Word64
-> Semaphore
-> Fence
-> ("pSwapchainImageCount" ::: Ptr Word32)
-> IO Result
mkVkAcquireNextImageKHRSafe


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkQueuePresentKHR
  :: FunPtr (Ptr Queue_T -> Ptr (SomeStruct PresentInfoKHR) -> IO Result) -> Ptr Queue_T -> Ptr (SomeStruct PresentInfoKHR) -> IO Result

-- | vkQueuePresentKHR - Queue an image for presentation
--
-- = Description
--
-- Note
--
-- There is no requirement for an application to present images in the same
-- order that they were acquired - applications can arbitrarily present any
-- image that is currently acquired.
--
-- == Valid Usage
--
-- -   Each element of @pSwapchains@ member of @pPresentInfo@ /must/ be a
--     swapchain that is created for a surface for which presentation is
--     supported from @queue@ as determined using a call to
--     'Vulkan.Extensions.VK_KHR_surface.getPhysicalDeviceSurfaceSupportKHR'
--
-- -   If more than one member of @pSwapchains@ was created from a display
--     surface, all display surfaces referenced that refer to the same
--     display /must/ use the same display mode
--
-- -   When a semaphore wait operation referring to a binary semaphore
--     defined by the elements of the @pWaitSemaphores@ member of
--     @pPresentInfo@ executes on @queue@, there /must/ be no other queues
--     waiting on the same semaphore
--
-- -   All elements of the @pWaitSemaphores@ member of @pPresentInfo@
--     /must/ be semaphores that are signaled, or have
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-semaphores-signaling semaphore signal operations>
--     previously submitted for execution
--
-- -   All elements of the @pWaitSemaphores@ member of @pPresentInfo@
--     /must/ be created with a
--     'Vulkan.Core12.Enums.SemaphoreType.SemaphoreType' of
--     'Vulkan.Core12.Enums.SemaphoreType.SEMAPHORE_TYPE_BINARY'
--
-- -   All elements of the @pWaitSemaphores@ member of @pPresentInfo@
--     /must/ reference a semaphore signal operation that has been
--     submitted for execution and any semaphore signal operations on which
--     it depends (if any) /must/ have also been submitted for execution
--
-- Any writes to memory backing the images referenced by the
-- @pImageIndices@ and @pSwapchains@ members of @pPresentInfo@, that are
-- available before 'queuePresentKHR' is executed, are automatically made
-- visible to the read access performed by the presentation engine. This
-- automatic visibility operation for an image happens-after the semaphore
-- signal operation, and happens-before the presentation engine accesses
-- the image.
--
-- Queueing an image for presentation defines a set of /queue operations/,
-- including waiting on the semaphores and submitting a presentation
-- request to the presentation engine. However, the scope of this set of
-- queue operations does not include the actual processing of the image by
-- the presentation engine.
--
-- Note
--
-- The origin of the native orientation of the surface coordinate system is
-- not specified in the Vulkan specification; it depends on the platform.
-- For most platforms the origin is by default upper-left, meaning the
-- pixel of the presented 'Vulkan.Core10.Handles.Image' at coordinates
-- (0,0) would appear at the upper left pixel of the platform surface
-- (assuming
-- 'Vulkan.Extensions.VK_KHR_surface.SURFACE_TRANSFORM_IDENTITY_BIT_KHR',
-- and the display standing the right way up).
--
-- If 'queuePresentKHR' fails to enqueue the corresponding set of queue
-- operations, it /may/ return
-- 'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY' or
-- 'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_DEVICE_MEMORY'. If it does, the
-- implementation /must/ ensure that the state and contents of any
-- resources or synchronization primitives referenced is unaffected by the
-- call or its failure.
--
-- If 'queuePresentKHR' fails in such a way that the implementation is
-- unable to make that guarantee, the implementation /must/ return
-- 'Vulkan.Core10.Enums.Result.ERROR_DEVICE_LOST'.
--
-- However, if the presentation request is rejected by the presentation
-- engine with an error 'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_DATE_KHR',
-- 'Vulkan.Core10.Enums.Result.ERROR_FULL_SCREEN_EXCLUSIVE_MODE_LOST_EXT',
-- or 'Vulkan.Core10.Enums.Result.ERROR_SURFACE_LOST_KHR', the set of queue
-- operations are still considered to be enqueued and thus any semaphore
-- wait operation specified in 'PresentInfoKHR' will execute when the
-- corresponding queue operation is complete.
--
-- If any @swapchain@ member of @pPresentInfo@ was created with
-- 'Vulkan.Extensions.VK_EXT_full_screen_exclusive.FULL_SCREEN_EXCLUSIVE_APPLICATION_CONTROLLED_EXT',
-- 'Vulkan.Core10.Enums.Result.ERROR_FULL_SCREEN_EXCLUSIVE_MODE_LOST_EXT'
-- will be returned if that swapchain does not have exclusive full-screen
-- access, possibly for implementation-specific reasons outside of the
-- application’s control.
--
-- == Valid Usage (Implicit)
--
-- -   @queue@ /must/ be a valid 'Vulkan.Core10.Handles.Queue' handle
--
-- -   @pPresentInfo@ /must/ be a valid pointer to a valid 'PresentInfoKHR'
--     structure
--
-- == Host Synchronization
--
-- -   Host access to @queue@ /must/ be externally synchronized
--
-- -   Host access to @pPresentInfo->pWaitSemaphores@[] /must/ be
--     externally synchronized
--
-- -   Host access to @pPresentInfo->pSwapchains@[] /must/ be externally
--     synchronized
--
-- == Command Properties
--
-- \'
--
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
-- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-types Pipeline Type> |
-- +============================================================================================================================+========================================================================================================================+=======================================================================================================================+=====================================================================================================================================+
-- | -                                                                                                                          | -                                                                                                                      | Any                                                                                                                   | -                                                                                                                                   |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- == Return Codes
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>]
--
--     -   'Vulkan.Core10.Enums.Result.SUCCESS'
--
--     -   'Vulkan.Core10.Enums.Result.SUBOPTIMAL_KHR'
--
-- [<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'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_DEVICE_LOST'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_DATE_KHR'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_SURFACE_LOST_KHR'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_FULL_SCREEN_EXCLUSIVE_MODE_LOST_EXT'
--
-- = See Also
--
-- 'PresentInfoKHR', 'Vulkan.Core10.Handles.Queue'
queuePresentKHR :: forall a io
                 . (Extendss PresentInfoKHR a, PokeChain a, MonadIO io)
                => -- | @queue@ is a queue that is capable of presentation to the target
                   -- surface’s platform on the same device as the image’s swapchain.
                   Queue
                -> -- | @pPresentInfo@ is a pointer to a 'PresentInfoKHR' structure specifying
                   -- parameters of the presentation.
                   (PresentInfoKHR a)
                -> io (Result)
queuePresentKHR :: Queue -> PresentInfoKHR a -> io Result
queuePresentKHR queue :: Queue
queue presentInfo :: PresentInfoKHR a
presentInfo = IO Result -> io Result
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Result -> io Result)
-> (ContT Result IO Result -> IO Result)
-> ContT Result IO Result
-> io Result
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT Result IO Result -> IO Result
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT Result IO Result -> io Result)
-> ContT Result IO Result -> io Result
forall a b. (a -> b) -> a -> b
$ do
  let vkQueuePresentKHRPtr :: FunPtr
  (Ptr Queue_T
   -> ("pPresentInfo" ::: Ptr (SomeStruct PresentInfoKHR))
   -> IO Result)
vkQueuePresentKHRPtr = DeviceCmds
-> FunPtr
     (Ptr Queue_T
      -> ("pPresentInfo" ::: Ptr (SomeStruct PresentInfoKHR))
      -> IO Result)
pVkQueuePresentKHR (Queue -> DeviceCmds
deviceCmds (Queue
queue :: Queue))
  IO () -> ContT Result IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT Result IO ()) -> IO () -> ContT Result IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Queue_T
   -> ("pPresentInfo" ::: Ptr (SomeStruct PresentInfoKHR))
   -> IO Result)
vkQueuePresentKHRPtr FunPtr
  (Ptr Queue_T
   -> ("pPresentInfo" ::: Ptr (SomeStruct PresentInfoKHR))
   -> IO Result)
-> FunPtr
     (Ptr Queue_T
      -> ("pPresentInfo" ::: Ptr (SomeStruct PresentInfoKHR))
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Queue_T
   -> ("pPresentInfo" ::: Ptr (SomeStruct PresentInfoKHR))
   -> 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 "" "The function pointer for vkQueuePresentKHR is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkQueuePresentKHR' :: Ptr Queue_T
-> ("pPresentInfo" ::: Ptr (SomeStruct PresentInfoKHR))
-> IO Result
vkQueuePresentKHR' = FunPtr
  (Ptr Queue_T
   -> ("pPresentInfo" ::: Ptr (SomeStruct PresentInfoKHR))
   -> IO Result)
-> Ptr Queue_T
-> ("pPresentInfo" ::: Ptr (SomeStruct PresentInfoKHR))
-> IO Result
mkVkQueuePresentKHR FunPtr
  (Ptr Queue_T
   -> ("pPresentInfo" ::: Ptr (SomeStruct PresentInfoKHR))
   -> IO Result)
vkQueuePresentKHRPtr
  Ptr (PresentInfoKHR a)
pPresentInfo <- ((Ptr (PresentInfoKHR a) -> IO Result) -> IO Result)
-> ContT Result IO (Ptr (PresentInfoKHR a))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (PresentInfoKHR a) -> IO Result) -> IO Result)
 -> ContT Result IO (Ptr (PresentInfoKHR a)))
-> ((Ptr (PresentInfoKHR a) -> IO Result) -> IO Result)
-> ContT Result IO (Ptr (PresentInfoKHR a))
forall a b. (a -> b) -> a -> b
$ PresentInfoKHR a
-> (Ptr (PresentInfoKHR a) -> IO Result) -> IO Result
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (PresentInfoKHR a
presentInfo)
  Result
r <- IO Result -> ContT Result IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT Result IO Result)
-> IO Result -> ContT Result IO Result
forall a b. (a -> b) -> a -> b
$ Ptr Queue_T
-> ("pPresentInfo" ::: Ptr (SomeStruct PresentInfoKHR))
-> IO Result
vkQueuePresentKHR' (Queue -> Ptr Queue_T
queueHandle (Queue
queue)) (Ptr (PresentInfoKHR a)
-> "pPresentInfo" ::: Ptr (SomeStruct PresentInfoKHR)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions Ptr (PresentInfoKHR a)
pPresentInfo)
  IO () -> ContT Result IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT Result IO ()) -> IO () -> ContT Result 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))
  Result -> ContT Result IO Result
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Result -> ContT Result IO Result)
-> Result -> ContT Result IO Result
forall a b. (a -> b) -> a -> b
$ (Result
r)


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkGetDeviceGroupPresentCapabilitiesKHR
  :: FunPtr (Ptr Device_T -> Ptr DeviceGroupPresentCapabilitiesKHR -> IO Result) -> Ptr Device_T -> Ptr DeviceGroupPresentCapabilitiesKHR -> IO Result

-- | vkGetDeviceGroupPresentCapabilitiesKHR - Query present capabilities from
-- other physical devices
--
-- == 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
--
-- 'Vulkan.Core10.Handles.Device', 'DeviceGroupPresentCapabilitiesKHR'
getDeviceGroupPresentCapabilitiesKHR :: forall io
                                      . (MonadIO io)
                                     => -- | @device@ is the logical device.
                                        --
                                        -- @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
                                        Device
                                     -> io (DeviceGroupPresentCapabilitiesKHR)
getDeviceGroupPresentCapabilitiesKHR :: Device -> io DeviceGroupPresentCapabilitiesKHR
getDeviceGroupPresentCapabilitiesKHR device :: Device
device = IO DeviceGroupPresentCapabilitiesKHR
-> io DeviceGroupPresentCapabilitiesKHR
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DeviceGroupPresentCapabilitiesKHR
 -> io DeviceGroupPresentCapabilitiesKHR)
-> (ContT
      DeviceGroupPresentCapabilitiesKHR
      IO
      DeviceGroupPresentCapabilitiesKHR
    -> IO DeviceGroupPresentCapabilitiesKHR)
-> ContT
     DeviceGroupPresentCapabilitiesKHR
     IO
     DeviceGroupPresentCapabilitiesKHR
-> io DeviceGroupPresentCapabilitiesKHR
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT
  DeviceGroupPresentCapabilitiesKHR
  IO
  DeviceGroupPresentCapabilitiesKHR
-> IO DeviceGroupPresentCapabilitiesKHR
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT
   DeviceGroupPresentCapabilitiesKHR
   IO
   DeviceGroupPresentCapabilitiesKHR
 -> io DeviceGroupPresentCapabilitiesKHR)
-> ContT
     DeviceGroupPresentCapabilitiesKHR
     IO
     DeviceGroupPresentCapabilitiesKHR
-> io DeviceGroupPresentCapabilitiesKHR
forall a b. (a -> b) -> a -> b
$ do
  let vkGetDeviceGroupPresentCapabilitiesKHRPtr :: FunPtr
  (Ptr Device_T
   -> ("pDeviceGroupPresentCapabilities"
       ::: Ptr DeviceGroupPresentCapabilitiesKHR)
   -> IO Result)
vkGetDeviceGroupPresentCapabilitiesKHRPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> ("pDeviceGroupPresentCapabilities"
          ::: Ptr DeviceGroupPresentCapabilitiesKHR)
      -> IO Result)
pVkGetDeviceGroupPresentCapabilitiesKHR (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  IO () -> ContT DeviceGroupPresentCapabilitiesKHR IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT DeviceGroupPresentCapabilitiesKHR IO ())
-> IO () -> ContT DeviceGroupPresentCapabilitiesKHR IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> ("pDeviceGroupPresentCapabilities"
       ::: Ptr DeviceGroupPresentCapabilitiesKHR)
   -> IO Result)
vkGetDeviceGroupPresentCapabilitiesKHRPtr FunPtr
  (Ptr Device_T
   -> ("pDeviceGroupPresentCapabilities"
       ::: Ptr DeviceGroupPresentCapabilitiesKHR)
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> ("pDeviceGroupPresentCapabilities"
          ::: Ptr DeviceGroupPresentCapabilitiesKHR)
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> ("pDeviceGroupPresentCapabilities"
       ::: Ptr DeviceGroupPresentCapabilitiesKHR)
   -> 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 "" "The function pointer for vkGetDeviceGroupPresentCapabilitiesKHR is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetDeviceGroupPresentCapabilitiesKHR' :: Ptr Device_T
-> ("pDeviceGroupPresentCapabilities"
    ::: Ptr DeviceGroupPresentCapabilitiesKHR)
-> IO Result
vkGetDeviceGroupPresentCapabilitiesKHR' = FunPtr
  (Ptr Device_T
   -> ("pDeviceGroupPresentCapabilities"
       ::: Ptr DeviceGroupPresentCapabilitiesKHR)
   -> IO Result)
-> Ptr Device_T
-> ("pDeviceGroupPresentCapabilities"
    ::: Ptr DeviceGroupPresentCapabilitiesKHR)
-> IO Result
mkVkGetDeviceGroupPresentCapabilitiesKHR FunPtr
  (Ptr Device_T
   -> ("pDeviceGroupPresentCapabilities"
       ::: Ptr DeviceGroupPresentCapabilitiesKHR)
   -> IO Result)
vkGetDeviceGroupPresentCapabilitiesKHRPtr
  "pDeviceGroupPresentCapabilities"
::: Ptr DeviceGroupPresentCapabilitiesKHR
pPDeviceGroupPresentCapabilities <- ((("pDeviceGroupPresentCapabilities"
   ::: Ptr DeviceGroupPresentCapabilitiesKHR)
  -> IO DeviceGroupPresentCapabilitiesKHR)
 -> IO DeviceGroupPresentCapabilitiesKHR)
-> ContT
     DeviceGroupPresentCapabilitiesKHR
     IO
     ("pDeviceGroupPresentCapabilities"
      ::: Ptr DeviceGroupPresentCapabilitiesKHR)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (forall b.
ToCStruct DeviceGroupPresentCapabilitiesKHR =>
(("pDeviceGroupPresentCapabilities"
  ::: Ptr DeviceGroupPresentCapabilitiesKHR)
 -> IO b)
-> IO b
forall a b. ToCStruct a => (Ptr a -> IO b) -> IO b
withZeroCStruct @DeviceGroupPresentCapabilitiesKHR)
  Result
r <- IO Result -> ContT DeviceGroupPresentCapabilitiesKHR IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT DeviceGroupPresentCapabilitiesKHR IO Result)
-> IO Result -> ContT DeviceGroupPresentCapabilitiesKHR IO Result
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> ("pDeviceGroupPresentCapabilities"
    ::: Ptr DeviceGroupPresentCapabilitiesKHR)
-> IO Result
vkGetDeviceGroupPresentCapabilitiesKHR' (Device -> Ptr Device_T
deviceHandle (Device
device)) ("pDeviceGroupPresentCapabilities"
::: Ptr DeviceGroupPresentCapabilitiesKHR
pPDeviceGroupPresentCapabilities)
  IO () -> ContT DeviceGroupPresentCapabilitiesKHR IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT DeviceGroupPresentCapabilitiesKHR IO ())
-> IO () -> ContT DeviceGroupPresentCapabilitiesKHR 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))
  DeviceGroupPresentCapabilitiesKHR
pDeviceGroupPresentCapabilities <- IO DeviceGroupPresentCapabilitiesKHR
-> ContT
     DeviceGroupPresentCapabilitiesKHR
     IO
     DeviceGroupPresentCapabilitiesKHR
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO DeviceGroupPresentCapabilitiesKHR
 -> ContT
      DeviceGroupPresentCapabilitiesKHR
      IO
      DeviceGroupPresentCapabilitiesKHR)
-> IO DeviceGroupPresentCapabilitiesKHR
-> ContT
     DeviceGroupPresentCapabilitiesKHR
     IO
     DeviceGroupPresentCapabilitiesKHR
forall a b. (a -> b) -> a -> b
$ ("pDeviceGroupPresentCapabilities"
 ::: Ptr DeviceGroupPresentCapabilitiesKHR)
-> IO DeviceGroupPresentCapabilitiesKHR
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @DeviceGroupPresentCapabilitiesKHR "pDeviceGroupPresentCapabilities"
::: Ptr DeviceGroupPresentCapabilitiesKHR
pPDeviceGroupPresentCapabilities
  DeviceGroupPresentCapabilitiesKHR
-> ContT
     DeviceGroupPresentCapabilitiesKHR
     IO
     DeviceGroupPresentCapabilitiesKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DeviceGroupPresentCapabilitiesKHR
 -> ContT
      DeviceGroupPresentCapabilitiesKHR
      IO
      DeviceGroupPresentCapabilitiesKHR)
-> DeviceGroupPresentCapabilitiesKHR
-> ContT
     DeviceGroupPresentCapabilitiesKHR
     IO
     DeviceGroupPresentCapabilitiesKHR
forall a b. (a -> b) -> a -> b
$ (DeviceGroupPresentCapabilitiesKHR
pDeviceGroupPresentCapabilities)


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkGetDeviceGroupSurfacePresentModesKHR
  :: FunPtr (Ptr Device_T -> SurfaceKHR -> Ptr DeviceGroupPresentModeFlagsKHR -> IO Result) -> Ptr Device_T -> SurfaceKHR -> Ptr DeviceGroupPresentModeFlagsKHR -> IO Result

-- | vkGetDeviceGroupSurfacePresentModesKHR - Query present capabilities for
-- a surface
--
-- = Description
--
-- The modes returned by this command are not invariant, and /may/ change
-- in response to the surface being moved, resized, or occluded. These
-- modes /must/ be a subset of the modes returned by
-- 'getDeviceGroupPresentCapabilitiesKHR'.
--
-- == Valid Usage (Implicit)
--
-- -   @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   @surface@ /must/ be a valid 'Vulkan.Extensions.Handles.SurfaceKHR'
--     handle
--
-- -   @pModes@ /must/ be a valid pointer to a
--     'DeviceGroupPresentModeFlagsKHR' value
--
-- -   Both of @device@, and @surface@ /must/ have been created, allocated,
--     or retrieved from the same 'Vulkan.Core10.Handles.Instance'
--
-- == Host Synchronization
--
-- -   Host access to @surface@ /must/ be externally synchronized
--
-- == 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'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_SURFACE_LOST_KHR'
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.Device', 'DeviceGroupPresentModeFlagsKHR',
-- 'Vulkan.Extensions.Handles.SurfaceKHR'
getDeviceGroupSurfacePresentModesKHR :: forall io
                                      . (MonadIO io)
                                     => -- | @device@ is the logical device.
                                        Device
                                     -> -- | @surface@ is the surface.
                                        SurfaceKHR
                                     -> io (("modes" ::: DeviceGroupPresentModeFlagsKHR))
getDeviceGroupSurfacePresentModesKHR :: Device
-> SurfaceKHR -> io ("modes" ::: DeviceGroupPresentModeFlagsKHR)
getDeviceGroupSurfacePresentModesKHR device :: Device
device surface :: SurfaceKHR
surface = IO ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> io ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ("modes" ::: DeviceGroupPresentModeFlagsKHR)
 -> io ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> (ContT
      ("modes" ::: DeviceGroupPresentModeFlagsKHR)
      IO
      ("modes" ::: DeviceGroupPresentModeFlagsKHR)
    -> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> ContT
     ("modes" ::: DeviceGroupPresentModeFlagsKHR)
     IO
     ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> io ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT
  ("modes" ::: DeviceGroupPresentModeFlagsKHR)
  IO
  ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT
   ("modes" ::: DeviceGroupPresentModeFlagsKHR)
   IO
   ("modes" ::: DeviceGroupPresentModeFlagsKHR)
 -> io ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> ContT
     ("modes" ::: DeviceGroupPresentModeFlagsKHR)
     IO
     ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> io ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall a b. (a -> b) -> a -> b
$ do
  let vkGetDeviceGroupSurfacePresentModesKHRPtr :: FunPtr
  (Ptr Device_T
   -> SurfaceKHR
   -> ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
   -> IO Result)
vkGetDeviceGroupSurfacePresentModesKHRPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> SurfaceKHR
      -> ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
      -> IO Result)
pVkGetDeviceGroupSurfacePresentModesKHR (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  IO () -> ContT ("modes" ::: DeviceGroupPresentModeFlagsKHR) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT ("modes" ::: DeviceGroupPresentModeFlagsKHR) IO ())
-> IO ()
-> ContT ("modes" ::: DeviceGroupPresentModeFlagsKHR) IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> SurfaceKHR
   -> ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
   -> IO Result)
vkGetDeviceGroupSurfacePresentModesKHRPtr FunPtr
  (Ptr Device_T
   -> SurfaceKHR
   -> ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> SurfaceKHR
      -> ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> SurfaceKHR
   -> ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
   -> 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 "" "The function pointer for vkGetDeviceGroupSurfacePresentModesKHR is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetDeviceGroupSurfacePresentModesKHR' :: Ptr Device_T
-> SurfaceKHR
-> ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> IO Result
vkGetDeviceGroupSurfacePresentModesKHR' = FunPtr
  (Ptr Device_T
   -> SurfaceKHR
   -> ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
   -> IO Result)
-> Ptr Device_T
-> SurfaceKHR
-> ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> IO Result
mkVkGetDeviceGroupSurfacePresentModesKHR FunPtr
  (Ptr Device_T
   -> SurfaceKHR
   -> ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
   -> IO Result)
vkGetDeviceGroupSurfacePresentModesKHRPtr
  "pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR)
pPModes <- ((("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
  -> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR))
 -> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> ContT
     ("modes" ::: DeviceGroupPresentModeFlagsKHR)
     IO
     ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
   -> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR))
  -> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR))
 -> ContT
      ("modes" ::: DeviceGroupPresentModeFlagsKHR)
      IO
      ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR)))
-> ((("pModes"
      ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
     -> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR))
    -> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> ContT
     ("modes" ::: DeviceGroupPresentModeFlagsKHR)
     IO
     ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
forall a b. (a -> b) -> a -> b
$ IO ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> (("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
    -> IO ())
-> (("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
    -> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int
-> IO
     ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
forall a. Int -> IO (Ptr a)
callocBytes @DeviceGroupPresentModeFlagsKHR 4) ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> IO ()
forall a. Ptr a -> IO ()
free
  Result
r <- IO Result
-> ContT ("modes" ::: DeviceGroupPresentModeFlagsKHR) IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result
 -> ContT ("modes" ::: DeviceGroupPresentModeFlagsKHR) IO Result)
-> IO Result
-> ContT ("modes" ::: DeviceGroupPresentModeFlagsKHR) IO Result
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> SurfaceKHR
-> ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> IO Result
vkGetDeviceGroupSurfacePresentModesKHR' (Device -> Ptr Device_T
deviceHandle (Device
device)) (SurfaceKHR
surface) ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR)
pPModes)
  IO () -> ContT ("modes" ::: DeviceGroupPresentModeFlagsKHR) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT ("modes" ::: DeviceGroupPresentModeFlagsKHR) IO ())
-> IO ()
-> ContT ("modes" ::: DeviceGroupPresentModeFlagsKHR) 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))
  "modes" ::: DeviceGroupPresentModeFlagsKHR
pModes <- IO ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ContT
     ("modes" ::: DeviceGroupPresentModeFlagsKHR)
     IO
     ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ("modes" ::: DeviceGroupPresentModeFlagsKHR)
 -> ContT
      ("modes" ::: DeviceGroupPresentModeFlagsKHR)
      IO
      ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ContT
     ("modes" ::: DeviceGroupPresentModeFlagsKHR)
     IO
     ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall a b. (a -> b) -> a -> b
$ ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall a. Storable a => Ptr a -> IO a
peek @DeviceGroupPresentModeFlagsKHR "pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR)
pPModes
  ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ContT
     ("modes" ::: DeviceGroupPresentModeFlagsKHR)
     IO
     ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (("modes" ::: DeviceGroupPresentModeFlagsKHR)
 -> ContT
      ("modes" ::: DeviceGroupPresentModeFlagsKHR)
      IO
      ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ContT
     ("modes" ::: DeviceGroupPresentModeFlagsKHR)
     IO
     ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall a b. (a -> b) -> a -> b
$ ("modes" ::: DeviceGroupPresentModeFlagsKHR
pModes)


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkAcquireNextImage2KHRUnsafe
  :: FunPtr (Ptr Device_T -> Ptr AcquireNextImageInfoKHR -> Ptr Word32 -> IO Result) -> Ptr Device_T -> Ptr AcquireNextImageInfoKHR -> Ptr Word32 -> IO Result

foreign import ccall
  "dynamic" mkVkAcquireNextImage2KHRSafe
  :: FunPtr (Ptr Device_T -> Ptr AcquireNextImageInfoKHR -> Ptr Word32 -> IO Result) -> Ptr Device_T -> Ptr AcquireNextImageInfoKHR -> Ptr Word32 -> IO Result

-- | acquireNextImage2KHR with selectable safeness
acquireNextImage2KHRSafeOrUnsafe :: forall io
                                  . (MonadIO io)
                                 => -- No documentation found for TopLevel ""
                                    (FunPtr (Ptr Device_T -> Ptr AcquireNextImageInfoKHR -> Ptr Word32 -> IO Result) -> Ptr Device_T -> Ptr AcquireNextImageInfoKHR -> Ptr Word32 -> IO Result)
                                 -> -- | @device@ is the device associated with @swapchain@.
                                    Device
                                 -> -- | @pAcquireInfo@ is a pointer to a 'AcquireNextImageInfoKHR' structure
                                    -- containing parameters of the acquire.
                                    ("acquireInfo" ::: AcquireNextImageInfoKHR)
                                 -> io (Result, ("imageIndex" ::: Word32))
acquireNextImage2KHRSafeOrUnsafe :: (FunPtr
   (Ptr Device_T
    -> Ptr AcquireNextImageInfoKHR
    -> ("pSwapchainImageCount" ::: Ptr Word32)
    -> IO Result)
 -> Ptr Device_T
 -> Ptr AcquireNextImageInfoKHR
 -> ("pSwapchainImageCount" ::: Ptr Word32)
 -> IO Result)
-> Device -> AcquireNextImageInfoKHR -> io (Result, Word32)
acquireNextImage2KHRSafeOrUnsafe mkVkAcquireNextImage2KHR :: FunPtr
  (Ptr Device_T
   -> Ptr AcquireNextImageInfoKHR
   -> ("pSwapchainImageCount" ::: Ptr Word32)
   -> IO Result)
-> Ptr Device_T
-> Ptr AcquireNextImageInfoKHR
-> ("pSwapchainImageCount" ::: Ptr Word32)
-> IO Result
mkVkAcquireNextImage2KHR device :: Device
device acquireInfo :: AcquireNextImageInfoKHR
acquireInfo = IO (Result, Word32) -> io (Result, Word32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Result, Word32) -> io (Result, Word32))
-> (ContT (Result, Word32) IO (Result, Word32)
    -> IO (Result, Word32))
-> ContT (Result, Word32) IO (Result, Word32)
-> io (Result, Word32)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT (Result, Word32) IO (Result, Word32) -> IO (Result, Word32)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT (Result, Word32) IO (Result, Word32) -> io (Result, Word32))
-> ContT (Result, Word32) IO (Result, Word32)
-> io (Result, Word32)
forall a b. (a -> b) -> a -> b
$ do
  let vkAcquireNextImage2KHRPtr :: FunPtr
  (Ptr Device_T
   -> Ptr AcquireNextImageInfoKHR
   -> ("pSwapchainImageCount" ::: Ptr Word32)
   -> IO Result)
vkAcquireNextImage2KHRPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> Ptr AcquireNextImageInfoKHR
      -> ("pSwapchainImageCount" ::: Ptr Word32)
      -> IO Result)
pVkAcquireNextImage2KHR (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  IO () -> ContT (Result, Word32) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (Result, Word32) IO ())
-> IO () -> ContT (Result, Word32) IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> Ptr AcquireNextImageInfoKHR
   -> ("pSwapchainImageCount" ::: Ptr Word32)
   -> IO Result)
vkAcquireNextImage2KHRPtr FunPtr
  (Ptr Device_T
   -> Ptr AcquireNextImageInfoKHR
   -> ("pSwapchainImageCount" ::: Ptr Word32)
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> Ptr AcquireNextImageInfoKHR
      -> ("pSwapchainImageCount" ::: Ptr Word32)
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> Ptr AcquireNextImageInfoKHR
   -> ("pSwapchainImageCount" ::: Ptr Word32)
   -> 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 "" "The function pointer for vkAcquireNextImage2KHR is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkAcquireNextImage2KHR' :: Ptr Device_T
-> Ptr AcquireNextImageInfoKHR
-> ("pSwapchainImageCount" ::: Ptr Word32)
-> IO Result
vkAcquireNextImage2KHR' = FunPtr
  (Ptr Device_T
   -> Ptr AcquireNextImageInfoKHR
   -> ("pSwapchainImageCount" ::: Ptr Word32)
   -> IO Result)
-> Ptr Device_T
-> Ptr AcquireNextImageInfoKHR
-> ("pSwapchainImageCount" ::: Ptr Word32)
-> IO Result
mkVkAcquireNextImage2KHR FunPtr
  (Ptr Device_T
   -> Ptr AcquireNextImageInfoKHR
   -> ("pSwapchainImageCount" ::: Ptr Word32)
   -> IO Result)
vkAcquireNextImage2KHRPtr
  Ptr AcquireNextImageInfoKHR
pAcquireInfo <- ((Ptr AcquireNextImageInfoKHR -> IO (Result, Word32))
 -> IO (Result, Word32))
-> ContT (Result, Word32) IO (Ptr AcquireNextImageInfoKHR)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr AcquireNextImageInfoKHR -> IO (Result, Word32))
  -> IO (Result, Word32))
 -> ContT (Result, Word32) IO (Ptr AcquireNextImageInfoKHR))
-> ((Ptr AcquireNextImageInfoKHR -> IO (Result, Word32))
    -> IO (Result, Word32))
-> ContT (Result, Word32) IO (Ptr AcquireNextImageInfoKHR)
forall a b. (a -> b) -> a -> b
$ AcquireNextImageInfoKHR
-> (Ptr AcquireNextImageInfoKHR -> IO (Result, Word32))
-> IO (Result, Word32)
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AcquireNextImageInfoKHR
acquireInfo)
  "pSwapchainImageCount" ::: Ptr Word32
pPImageIndex <- ((("pSwapchainImageCount" ::: Ptr Word32) -> IO (Result, Word32))
 -> IO (Result, Word32))
-> ContT
     (Result, Word32) IO ("pSwapchainImageCount" ::: Ptr Word32)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pSwapchainImageCount" ::: Ptr Word32) -> IO (Result, Word32))
  -> IO (Result, Word32))
 -> ContT
      (Result, Word32) IO ("pSwapchainImageCount" ::: Ptr Word32))
-> ((("pSwapchainImageCount" ::: Ptr Word32)
     -> IO (Result, Word32))
    -> IO (Result, Word32))
-> ContT
     (Result, Word32) IO ("pSwapchainImageCount" ::: Ptr Word32)
forall a b. (a -> b) -> a -> b
$ IO ("pSwapchainImageCount" ::: Ptr Word32)
-> (("pSwapchainImageCount" ::: Ptr Word32) -> IO ())
-> (("pSwapchainImageCount" ::: Ptr Word32) -> IO (Result, Word32))
-> IO (Result, Word32)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pSwapchainImageCount" ::: Ptr Word32)
forall a. Int -> IO (Ptr a)
callocBytes @Word32 4) ("pSwapchainImageCount" ::: Ptr Word32) -> IO ()
forall a. Ptr a -> IO ()
free
  Result
r <- IO Result -> ContT (Result, Word32) IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT (Result, Word32) IO Result)
-> IO Result -> ContT (Result, Word32) IO Result
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> Ptr AcquireNextImageInfoKHR
-> ("pSwapchainImageCount" ::: Ptr Word32)
-> IO Result
vkAcquireNextImage2KHR' (Device -> Ptr Device_T
deviceHandle (Device
device)) Ptr AcquireNextImageInfoKHR
pAcquireInfo ("pSwapchainImageCount" ::: Ptr Word32
pPImageIndex)
  IO () -> ContT (Result, Word32) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (Result, Word32) IO ())
-> IO () -> ContT (Result, Word32) 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))
  Word32
pImageIndex <- IO Word32 -> ContT (Result, Word32) IO Word32
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Word32 -> ContT (Result, Word32) IO Word32)
-> IO Word32 -> ContT (Result, Word32) IO Word32
forall a b. (a -> b) -> a -> b
$ ("pSwapchainImageCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 "pSwapchainImageCount" ::: Ptr Word32
pPImageIndex
  (Result, Word32) -> ContT (Result, Word32) IO (Result, Word32)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Result, Word32) -> ContT (Result, Word32) IO (Result, Word32))
-> (Result, Word32) -> ContT (Result, Word32) IO (Result, Word32)
forall a b. (a -> b) -> a -> b
$ (Result
r, Word32
pImageIndex)

-- | vkAcquireNextImage2KHR - Retrieve the index of the next available
-- presentable image
--
-- == Valid Usage
--
-- -   If the number of currently acquired images is greater than the
--     difference between the number of images in the @swapchain@ member of
--     @pAcquireInfo@ and the value of
--     'Vulkan.Extensions.VK_KHR_surface.SurfaceCapabilitiesKHR'::@minImageCount@
--     as returned by a call to
--     'Vulkan.Extensions.VK_KHR_get_surface_capabilities2.getPhysicalDeviceSurfaceCapabilities2KHR'
--     with the @surface@ used to create @swapchain@, the @timeout@ member
--     of @pAcquireInfo@ /must/ not be @UINT64_MAX@
--
-- == Valid Usage (Implicit)
--
-- -   @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   @pAcquireInfo@ /must/ be a valid pointer to a valid
--     'AcquireNextImageInfoKHR' structure
--
-- -   @pImageIndex@ /must/ be a valid pointer to a @uint32_t@ value
--
-- == Return Codes
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>]
--
--     -   'Vulkan.Core10.Enums.Result.SUCCESS'
--
--     -   'Vulkan.Core10.Enums.Result.TIMEOUT'
--
--     -   'Vulkan.Core10.Enums.Result.NOT_READY'
--
--     -   'Vulkan.Core10.Enums.Result.SUBOPTIMAL_KHR'
--
-- [<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'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_DEVICE_LOST'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_DATE_KHR'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_SURFACE_LOST_KHR'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_FULL_SCREEN_EXCLUSIVE_MODE_LOST_EXT'
--
-- = See Also
--
-- 'AcquireNextImageInfoKHR', 'Vulkan.Core10.Handles.Device'
acquireNextImage2KHR :: forall io
                      . (MonadIO io)
                     => -- | @device@ is the device associated with @swapchain@.
                        Device
                     -> -- | @pAcquireInfo@ is a pointer to a 'AcquireNextImageInfoKHR' structure
                        -- containing parameters of the acquire.
                        ("acquireInfo" ::: AcquireNextImageInfoKHR)
                     -> io (Result, ("imageIndex" ::: Word32))
acquireNextImage2KHR :: Device -> AcquireNextImageInfoKHR -> io (Result, Word32)
acquireNextImage2KHR = (FunPtr
   (Ptr Device_T
    -> Ptr AcquireNextImageInfoKHR
    -> ("pSwapchainImageCount" ::: Ptr Word32)
    -> IO Result)
 -> Ptr Device_T
 -> Ptr AcquireNextImageInfoKHR
 -> ("pSwapchainImageCount" ::: Ptr Word32)
 -> IO Result)
-> Device -> AcquireNextImageInfoKHR -> io (Result, Word32)
forall (io :: * -> *).
MonadIO io =>
(FunPtr
   (Ptr Device_T
    -> Ptr AcquireNextImageInfoKHR
    -> ("pSwapchainImageCount" ::: Ptr Word32)
    -> IO Result)
 -> Ptr Device_T
 -> Ptr AcquireNextImageInfoKHR
 -> ("pSwapchainImageCount" ::: Ptr Word32)
 -> IO Result)
-> Device -> AcquireNextImageInfoKHR -> io (Result, Word32)
acquireNextImage2KHRSafeOrUnsafe FunPtr
  (Ptr Device_T
   -> Ptr AcquireNextImageInfoKHR
   -> ("pSwapchainImageCount" ::: Ptr Word32)
   -> IO Result)
-> Ptr Device_T
-> Ptr AcquireNextImageInfoKHR
-> ("pSwapchainImageCount" ::: Ptr Word32)
-> IO Result
mkVkAcquireNextImage2KHRUnsafe

-- | A variant of 'acquireNextImage2KHR' which makes a *safe* FFI call
acquireNextImage2KHRSafe :: forall io
                          . (MonadIO io)
                         => -- | @device@ is the device associated with @swapchain@.
                            Device
                         -> -- | @pAcquireInfo@ is a pointer to a 'AcquireNextImageInfoKHR' structure
                            -- containing parameters of the acquire.
                            ("acquireInfo" ::: AcquireNextImageInfoKHR)
                         -> io (Result, ("imageIndex" ::: Word32))
acquireNextImage2KHRSafe :: Device -> AcquireNextImageInfoKHR -> io (Result, Word32)
acquireNextImage2KHRSafe = (FunPtr
   (Ptr Device_T
    -> Ptr AcquireNextImageInfoKHR
    -> ("pSwapchainImageCount" ::: Ptr Word32)
    -> IO Result)
 -> Ptr Device_T
 -> Ptr AcquireNextImageInfoKHR
 -> ("pSwapchainImageCount" ::: Ptr Word32)
 -> IO Result)
-> Device -> AcquireNextImageInfoKHR -> io (Result, Word32)
forall (io :: * -> *).
MonadIO io =>
(FunPtr
   (Ptr Device_T
    -> Ptr AcquireNextImageInfoKHR
    -> ("pSwapchainImageCount" ::: Ptr Word32)
    -> IO Result)
 -> Ptr Device_T
 -> Ptr AcquireNextImageInfoKHR
 -> ("pSwapchainImageCount" ::: Ptr Word32)
 -> IO Result)
-> Device -> AcquireNextImageInfoKHR -> io (Result, Word32)
acquireNextImage2KHRSafeOrUnsafe FunPtr
  (Ptr Device_T
   -> Ptr AcquireNextImageInfoKHR
   -> ("pSwapchainImageCount" ::: Ptr Word32)
   -> IO Result)
-> Ptr Device_T
-> Ptr AcquireNextImageInfoKHR
-> ("pSwapchainImageCount" ::: Ptr Word32)
-> IO Result
mkVkAcquireNextImage2KHRSafe


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkGetPhysicalDevicePresentRectanglesKHR
  :: FunPtr (Ptr PhysicalDevice_T -> SurfaceKHR -> Ptr Word32 -> Ptr Rect2D -> IO Result) -> Ptr PhysicalDevice_T -> SurfaceKHR -> Ptr Word32 -> Ptr Rect2D -> IO Result

-- | vkGetPhysicalDevicePresentRectanglesKHR - Query present rectangles for a
-- surface on a physical device
--
-- = Description
--
-- If @pRects@ is @NULL@, then the number of rectangles used when
-- presenting the given @surface@ is returned in @pRectCount@. Otherwise,
-- @pRectCount@ /must/ point to a variable set by the user to the number of
-- elements in the @pRects@ array, and on return the variable is
-- overwritten with the number of structures actually written to @pRects@.
-- If the value of @pRectCount@ is less than the number of rectangles, at
-- most @pRectCount@ structures will be written. If @pRectCount@ is smaller
-- than the number of rectangles used for the given @surface@,
-- 'Vulkan.Core10.Enums.Result.INCOMPLETE' will be returned instead of
-- 'Vulkan.Core10.Enums.Result.SUCCESS' to indicate that not all the
-- available values were returned.
--
-- The values returned by this command are not invariant, and /may/ change
-- in response to the surface being moved, resized, or occluded.
--
-- The rectangles returned by this command /must/ not overlap.
--
-- == Valid Usage (Implicit)
--
-- -   @physicalDevice@ /must/ be a valid
--     'Vulkan.Core10.Handles.PhysicalDevice' handle
--
-- -   @surface@ /must/ be a valid 'Vulkan.Extensions.Handles.SurfaceKHR'
--     handle
--
-- -   @pRectCount@ /must/ be a valid pointer to a @uint32_t@ value
--
-- -   If the value referenced by @pRectCount@ is not @0@, and @pRects@ is
--     not @NULL@, @pRects@ /must/ be a valid pointer to an array of
--     @pRectCount@ 'Vulkan.Core10.FundamentalTypes.Rect2D' structures
--
-- -   Both of @physicalDevice@, and @surface@ /must/ have been created,
--     allocated, or retrieved from the same
--     'Vulkan.Core10.Handles.Instance'
--
-- == Host Synchronization
--
-- -   Host access to @surface@ /must/ be externally synchronized
--
-- == Return Codes
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>]
--
--     -   'Vulkan.Core10.Enums.Result.SUCCESS'
--
--     -   'Vulkan.Core10.Enums.Result.INCOMPLETE'
--
-- [<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
--
-- 'Vulkan.Core10.Handles.PhysicalDevice',
-- 'Vulkan.Core10.FundamentalTypes.Rect2D',
-- 'Vulkan.Extensions.Handles.SurfaceKHR'
getPhysicalDevicePresentRectanglesKHR :: forall io
                                       . (MonadIO io)
                                      => -- | @physicalDevice@ is the physical device.
                                         PhysicalDevice
                                      -> -- | @surface@ is the surface.
                                         SurfaceKHR
                                      -> io (Result, ("rects" ::: Vector Rect2D))
getPhysicalDevicePresentRectanglesKHR :: PhysicalDevice
-> SurfaceKHR -> io (Result, "rects" ::: Vector Rect2D)
getPhysicalDevicePresentRectanglesKHR physicalDevice :: PhysicalDevice
physicalDevice surface :: SurfaceKHR
surface = IO (Result, "rects" ::: Vector Rect2D)
-> io (Result, "rects" ::: Vector Rect2D)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Result, "rects" ::: Vector Rect2D)
 -> io (Result, "rects" ::: Vector Rect2D))
-> (ContT
      (Result, "rects" ::: Vector Rect2D)
      IO
      (Result, "rects" ::: Vector Rect2D)
    -> IO (Result, "rects" ::: Vector Rect2D))
-> ContT
     (Result, "rects" ::: Vector Rect2D)
     IO
     (Result, "rects" ::: Vector Rect2D)
-> io (Result, "rects" ::: Vector Rect2D)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT
  (Result, "rects" ::: Vector Rect2D)
  IO
  (Result, "rects" ::: Vector Rect2D)
-> IO (Result, "rects" ::: Vector Rect2D)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT
   (Result, "rects" ::: Vector Rect2D)
   IO
   (Result, "rects" ::: Vector Rect2D)
 -> io (Result, "rects" ::: Vector Rect2D))
-> ContT
     (Result, "rects" ::: Vector Rect2D)
     IO
     (Result, "rects" ::: Vector Rect2D)
-> io (Result, "rects" ::: Vector Rect2D)
forall a b. (a -> b) -> a -> b
$ do
  let vkGetPhysicalDevicePresentRectanglesKHRPtr :: FunPtr
  (Ptr PhysicalDevice_T
   -> SurfaceKHR
   -> ("pSwapchainImageCount" ::: Ptr Word32)
   -> ("pRects" ::: Ptr Rect2D)
   -> IO Result)
vkGetPhysicalDevicePresentRectanglesKHRPtr = InstanceCmds
-> FunPtr
     (Ptr PhysicalDevice_T
      -> SurfaceKHR
      -> ("pSwapchainImageCount" ::: Ptr Word32)
      -> ("pRects" ::: Ptr Rect2D)
      -> IO Result)
pVkGetPhysicalDevicePresentRectanglesKHR (PhysicalDevice -> InstanceCmds
instanceCmds (PhysicalDevice
physicalDevice :: PhysicalDevice))
  IO () -> ContT (Result, "rects" ::: Vector Rect2D) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (Result, "rects" ::: Vector Rect2D) IO ())
-> IO () -> ContT (Result, "rects" ::: Vector Rect2D) IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr PhysicalDevice_T
   -> SurfaceKHR
   -> ("pSwapchainImageCount" ::: Ptr Word32)
   -> ("pRects" ::: Ptr Rect2D)
   -> IO Result)
vkGetPhysicalDevicePresentRectanglesKHRPtr FunPtr
  (Ptr PhysicalDevice_T
   -> SurfaceKHR
   -> ("pSwapchainImageCount" ::: Ptr Word32)
   -> ("pRects" ::: Ptr Rect2D)
   -> IO Result)
-> FunPtr
     (Ptr PhysicalDevice_T
      -> SurfaceKHR
      -> ("pSwapchainImageCount" ::: Ptr Word32)
      -> ("pRects" ::: Ptr Rect2D)
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr PhysicalDevice_T
   -> SurfaceKHR
   -> ("pSwapchainImageCount" ::: Ptr Word32)
   -> ("pRects" ::: Ptr Rect2D)
   -> 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 "" "The function pointer for vkGetPhysicalDevicePresentRectanglesKHR is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetPhysicalDevicePresentRectanglesKHR' :: Ptr PhysicalDevice_T
-> SurfaceKHR
-> ("pSwapchainImageCount" ::: Ptr Word32)
-> ("pRects" ::: Ptr Rect2D)
-> IO Result
vkGetPhysicalDevicePresentRectanglesKHR' = FunPtr
  (Ptr PhysicalDevice_T
   -> SurfaceKHR
   -> ("pSwapchainImageCount" ::: Ptr Word32)
   -> ("pRects" ::: Ptr Rect2D)
   -> IO Result)
-> Ptr PhysicalDevice_T
-> SurfaceKHR
-> ("pSwapchainImageCount" ::: Ptr Word32)
-> ("pRects" ::: Ptr Rect2D)
-> IO Result
mkVkGetPhysicalDevicePresentRectanglesKHR FunPtr
  (Ptr PhysicalDevice_T
   -> SurfaceKHR
   -> ("pSwapchainImageCount" ::: Ptr Word32)
   -> ("pRects" ::: Ptr Rect2D)
   -> IO Result)
vkGetPhysicalDevicePresentRectanglesKHRPtr
  let physicalDevice' :: Ptr PhysicalDevice_T
physicalDevice' = PhysicalDevice -> Ptr PhysicalDevice_T
physicalDeviceHandle (PhysicalDevice
physicalDevice)
  "pSwapchainImageCount" ::: Ptr Word32
pPRectCount <- ((("pSwapchainImageCount" ::: Ptr Word32)
  -> IO (Result, "rects" ::: Vector Rect2D))
 -> IO (Result, "rects" ::: Vector Rect2D))
-> ContT
     (Result, "rects" ::: Vector Rect2D)
     IO
     ("pSwapchainImageCount" ::: Ptr Word32)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pSwapchainImageCount" ::: Ptr Word32)
   -> IO (Result, "rects" ::: Vector Rect2D))
  -> IO (Result, "rects" ::: Vector Rect2D))
 -> ContT
      (Result, "rects" ::: Vector Rect2D)
      IO
      ("pSwapchainImageCount" ::: Ptr Word32))
-> ((("pSwapchainImageCount" ::: Ptr Word32)
     -> IO (Result, "rects" ::: Vector Rect2D))
    -> IO (Result, "rects" ::: Vector Rect2D))
-> ContT
     (Result, "rects" ::: Vector Rect2D)
     IO
     ("pSwapchainImageCount" ::: Ptr Word32)
forall a b. (a -> b) -> a -> b
$ IO ("pSwapchainImageCount" ::: Ptr Word32)
-> (("pSwapchainImageCount" ::: Ptr Word32) -> IO ())
-> (("pSwapchainImageCount" ::: Ptr Word32)
    -> IO (Result, "rects" ::: Vector Rect2D))
-> IO (Result, "rects" ::: Vector Rect2D)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pSwapchainImageCount" ::: Ptr Word32)
forall a. Int -> IO (Ptr a)
callocBytes @Word32 4) ("pSwapchainImageCount" ::: Ptr Word32) -> IO ()
forall a. Ptr a -> IO ()
free
  Result
r <- IO Result -> ContT (Result, "rects" ::: Vector Rect2D) IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT (Result, "rects" ::: Vector Rect2D) IO Result)
-> IO Result -> ContT (Result, "rects" ::: Vector Rect2D) IO Result
forall a b. (a -> b) -> a -> b
$ Ptr PhysicalDevice_T
-> SurfaceKHR
-> ("pSwapchainImageCount" ::: Ptr Word32)
-> ("pRects" ::: Ptr Rect2D)
-> IO Result
vkGetPhysicalDevicePresentRectanglesKHR' Ptr PhysicalDevice_T
physicalDevice' (SurfaceKHR
surface) ("pSwapchainImageCount" ::: Ptr Word32
pPRectCount) ("pRects" ::: Ptr Rect2D
forall a. Ptr a
nullPtr)
  IO () -> ContT (Result, "rects" ::: Vector Rect2D) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (Result, "rects" ::: Vector Rect2D) IO ())
-> IO () -> ContT (Result, "rects" ::: Vector Rect2D) 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))
  Word32
pRectCount <- IO Word32 -> ContT (Result, "rects" ::: Vector Rect2D) IO Word32
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Word32 -> ContT (Result, "rects" ::: Vector Rect2D) IO Word32)
-> IO Word32 -> ContT (Result, "rects" ::: Vector Rect2D) IO Word32
forall a b. (a -> b) -> a -> b
$ ("pSwapchainImageCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 "pSwapchainImageCount" ::: Ptr Word32
pPRectCount
  "pRects" ::: Ptr Rect2D
pPRects <- ((("pRects" ::: Ptr Rect2D)
  -> IO (Result, "rects" ::: Vector Rect2D))
 -> IO (Result, "rects" ::: Vector Rect2D))
-> ContT
     (Result, "rects" ::: Vector Rect2D) IO ("pRects" ::: Ptr Rect2D)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pRects" ::: Ptr Rect2D)
   -> IO (Result, "rects" ::: Vector Rect2D))
  -> IO (Result, "rects" ::: Vector Rect2D))
 -> ContT
      (Result, "rects" ::: Vector Rect2D) IO ("pRects" ::: Ptr Rect2D))
-> ((("pRects" ::: Ptr Rect2D)
     -> IO (Result, "rects" ::: Vector Rect2D))
    -> IO (Result, "rects" ::: Vector Rect2D))
-> ContT
     (Result, "rects" ::: Vector Rect2D) IO ("pRects" ::: Ptr Rect2D)
forall a b. (a -> b) -> a -> b
$ IO ("pRects" ::: Ptr Rect2D)
-> (("pRects" ::: Ptr Rect2D) -> IO ())
-> (("pRects" ::: Ptr Rect2D)
    -> IO (Result, "rects" ::: Vector Rect2D))
-> IO (Result, "rects" ::: Vector Rect2D)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pRects" ::: Ptr Rect2D)
forall a. Int -> IO (Ptr a)
callocBytes @Rect2D ((Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pRectCount)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 16)) ("pRects" ::: Ptr Rect2D) -> IO ()
forall a. Ptr a -> IO ()
free
  [()]
_ <- (Int -> ContT (Result, "rects" ::: Vector Rect2D) IO ())
-> [Int] -> ContT (Result, "rects" ::: Vector Rect2D) IO [()]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (\i :: Int
i -> ((() -> IO (Result, "rects" ::: Vector Rect2D))
 -> IO (Result, "rects" ::: Vector Rect2D))
-> ContT (Result, "rects" ::: Vector Rect2D) IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO (Result, "rects" ::: Vector Rect2D))
  -> IO (Result, "rects" ::: Vector Rect2D))
 -> ContT (Result, "rects" ::: Vector Rect2D) IO ())
-> ((() -> IO (Result, "rects" ::: Vector Rect2D))
    -> IO (Result, "rects" ::: Vector Rect2D))
-> ContT (Result, "rects" ::: Vector Rect2D) IO ()
forall a b. (a -> b) -> a -> b
$ ("pRects" ::: Ptr Rect2D)
-> IO (Result, "rects" ::: Vector Rect2D)
-> IO (Result, "rects" ::: Vector Rect2D)
forall a b. ToCStruct a => Ptr a -> IO b -> IO b
pokeZeroCStruct ("pRects" ::: Ptr Rect2D
pPRects ("pRects" ::: Ptr Rect2D) -> Int -> "pRects" ::: Ptr Rect2D
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
* 16) :: Ptr Rect2D) (IO (Result, "rects" ::: Vector Rect2D)
 -> IO (Result, "rects" ::: Vector Rect2D))
-> ((() -> IO (Result, "rects" ::: Vector Rect2D))
    -> IO (Result, "rects" ::: Vector Rect2D))
-> (() -> IO (Result, "rects" ::: Vector Rect2D))
-> IO (Result, "rects" ::: Vector Rect2D)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO (Result, "rects" ::: Vector Rect2D))
-> () -> IO (Result, "rects" ::: Vector Rect2D)
forall a b. (a -> b) -> a -> b
$ ())) [0..(Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pRectCount)) Int -> Int -> Int
forall a. Num a => a -> a -> a
- 1]
  Result
r' <- IO Result -> ContT (Result, "rects" ::: Vector Rect2D) IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT (Result, "rects" ::: Vector Rect2D) IO Result)
-> IO Result -> ContT (Result, "rects" ::: Vector Rect2D) IO Result
forall a b. (a -> b) -> a -> b
$ Ptr PhysicalDevice_T
-> SurfaceKHR
-> ("pSwapchainImageCount" ::: Ptr Word32)
-> ("pRects" ::: Ptr Rect2D)
-> IO Result
vkGetPhysicalDevicePresentRectanglesKHR' Ptr PhysicalDevice_T
physicalDevice' (SurfaceKHR
surface) ("pSwapchainImageCount" ::: Ptr Word32
pPRectCount) (("pRects" ::: Ptr Rect2D
pPRects))
  IO () -> ContT (Result, "rects" ::: Vector Rect2D) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (Result, "rects" ::: Vector Rect2D) IO ())
-> IO () -> ContT (Result, "rects" ::: Vector Rect2D) 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'))
  Word32
pRectCount' <- IO Word32 -> ContT (Result, "rects" ::: Vector Rect2D) IO Word32
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Word32 -> ContT (Result, "rects" ::: Vector Rect2D) IO Word32)
-> IO Word32 -> ContT (Result, "rects" ::: Vector Rect2D) IO Word32
forall a b. (a -> b) -> a -> b
$ ("pSwapchainImageCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 "pSwapchainImageCount" ::: Ptr Word32
pPRectCount
  "rects" ::: Vector Rect2D
pRects' <- IO ("rects" ::: Vector Rect2D)
-> ContT
     (Result, "rects" ::: Vector Rect2D) IO ("rects" ::: Vector Rect2D)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ("rects" ::: Vector Rect2D)
 -> ContT
      (Result, "rects" ::: Vector Rect2D) IO ("rects" ::: Vector Rect2D))
-> IO ("rects" ::: Vector Rect2D)
-> ContT
     (Result, "rects" ::: Vector Rect2D) IO ("rects" ::: Vector Rect2D)
forall a b. (a -> b) -> a -> b
$ Int -> (Int -> IO Rect2D) -> IO ("rects" ::: Vector Rect2D)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pRectCount')) (\i :: Int
i -> ("pRects" ::: Ptr Rect2D) -> IO Rect2D
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Rect2D ((("pRects" ::: Ptr Rect2D
pPRects) ("pRects" ::: Ptr Rect2D) -> Int -> "pRects" ::: Ptr Rect2D
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (16 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Rect2D)))
  (Result, "rects" ::: Vector Rect2D)
-> ContT
     (Result, "rects" ::: Vector Rect2D)
     IO
     (Result, "rects" ::: Vector Rect2D)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Result, "rects" ::: Vector Rect2D)
 -> ContT
      (Result, "rects" ::: Vector Rect2D)
      IO
      (Result, "rects" ::: Vector Rect2D))
-> (Result, "rects" ::: Vector Rect2D)
-> ContT
     (Result, "rects" ::: Vector Rect2D)
     IO
     (Result, "rects" ::: Vector Rect2D)
forall a b. (a -> b) -> a -> b
$ ((Result
r'), "rects" ::: Vector Rect2D
pRects')


-- | VkSwapchainCreateInfoKHR - Structure specifying parameters of a newly
-- created swapchain object
--
-- = Description
--
-- Note
--
-- On some platforms, it is normal that @maxImageExtent@ /may/ become @(0,
-- 0)@, for example when the window is minimized. In such a case, it is not
-- possible to create a swapchain due to the Valid Usage requirements.
--
-- -   @imageArrayLayers@ is the number of views in a multiview\/stereo
--     surface. For non-stereoscopic-3D applications, this value is 1.
--
-- -   @imageUsage@ is a bitmask of
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.ImageUsageFlagBits'
--     describing the intended usage of the (acquired) swapchain images.
--
-- -   @imageSharingMode@ is the sharing mode used for the image(s) of the
--     swapchain.
--
-- -   @queueFamilyIndexCount@ is the number of queue families having
--     access to the image(s) of the swapchain when @imageSharingMode@ is
--     'Vulkan.Core10.Enums.SharingMode.SHARING_MODE_CONCURRENT'.
--
-- -   @pQueueFamilyIndices@ is a pointer to an array of queue family
--     indices having access to the images(s) of the swapchain when
--     @imageSharingMode@ is
--     'Vulkan.Core10.Enums.SharingMode.SHARING_MODE_CONCURRENT'.
--
-- -   @preTransform@ is a
--     'Vulkan.Extensions.VK_KHR_surface.SurfaceTransformFlagBitsKHR' value
--     describing the transform, relative to the presentation engine’s
--     natural orientation, applied to the image content prior to
--     presentation. If it does not match the @currentTransform@ value
--     returned by
--     'Vulkan.Extensions.VK_KHR_surface.getPhysicalDeviceSurfaceCapabilitiesKHR',
--     the presentation engine will transform the image content as part of
--     the presentation operation.
--
-- -   @compositeAlpha@ is a
--     'Vulkan.Extensions.VK_KHR_surface.CompositeAlphaFlagBitsKHR' value
--     indicating the alpha compositing mode to use when this surface is
--     composited together with other surfaces on certain window systems.
--
-- -   @presentMode@ is the presentation mode the swapchain will use. A
--     swapchain’s present mode determines how incoming present requests
--     will be processed and queued internally.
--
-- -   @clipped@ specifies whether the Vulkan implementation is allowed to
--     discard rendering operations that affect regions of the surface that
--     are not visible.
--
--     -   If set to 'Vulkan.Core10.FundamentalTypes.TRUE', the presentable
--         images associated with the swapchain /may/ not own all of their
--         pixels. Pixels in the presentable images that correspond to
--         regions of the target surface obscured by another window on the
--         desktop, or subject to some other clipping mechanism will have
--         undefined content when read back. Fragment shaders /may/ not
--         execute for these pixels, and thus any side effects they would
--         have had will not occur. 'Vulkan.Core10.FundamentalTypes.TRUE'
--         value does not guarantee any clipping will occur, but allows
--         more optimal presentation methods to be used on some platforms.
--
--     -   If set to 'Vulkan.Core10.FundamentalTypes.FALSE', presentable
--         images associated with the swapchain will own all of the pixels
--         they contain.
--
-- Note
--
-- Applications /should/ set this value to
-- 'Vulkan.Core10.FundamentalTypes.TRUE' if they do not expect to read back
-- the content of presentable images before presenting them or after
-- reacquiring them, and if their fragment shaders do not have any side
-- effects that require them to run for all pixels in the presentable
-- image.
--
-- -   @oldSwapchain@ is 'Vulkan.Core10.APIConstants.NULL_HANDLE', or the
--     existing non-retired swapchain currently associated with @surface@.
--     Providing a valid @oldSwapchain@ /may/ aid in the resource reuse,
--     and also allows the application to still present any images that are
--     already acquired from it.
--
-- Upon calling 'createSwapchainKHR' with an @oldSwapchain@ that is not
-- 'Vulkan.Core10.APIConstants.NULL_HANDLE', @oldSwapchain@ is
-- retired — even if creation of the new swapchain fails. The new swapchain
-- is created in the non-retired state whether or not @oldSwapchain@ is
-- 'Vulkan.Core10.APIConstants.NULL_HANDLE'.
--
-- Upon calling 'createSwapchainKHR' with an @oldSwapchain@ that is not
-- 'Vulkan.Core10.APIConstants.NULL_HANDLE', any images from @oldSwapchain@
-- that are not acquired by the application /may/ be freed by the
-- implementation, which /may/ occur even if creation of the new swapchain
-- fails. The application /can/ destroy @oldSwapchain@ to free all memory
-- associated with @oldSwapchain@.
--
-- Note
--
-- Multiple retired swapchains /can/ be associated with the same
-- 'Vulkan.Extensions.Handles.SurfaceKHR' through multiple uses of
-- @oldSwapchain@ that outnumber calls to 'destroySwapchainKHR'.
--
-- After @oldSwapchain@ is retired, the application /can/ pass to
-- 'queuePresentKHR' any images it had already acquired from
-- @oldSwapchain@. E.g., an application may present an image from the old
-- swapchain before an image from the new swapchain is ready to be
-- presented. As usual, 'queuePresentKHR' /may/ fail if @oldSwapchain@ has
-- entered a state that causes
-- 'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_DATE_KHR' to be returned.
--
-- The application /can/ continue to use a shared presentable image
-- obtained from @oldSwapchain@ until a presentable image is acquired from
-- the new swapchain, as long as it has not entered a state that causes it
-- to return 'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_DATE_KHR'.
--
-- == Valid Usage
--
-- -   @surface@ /must/ be a surface that is supported by the device as
--     determined using
--     'Vulkan.Extensions.VK_KHR_surface.getPhysicalDeviceSurfaceSupportKHR'
--
-- -   @minImageCount@ /must/ be less than or equal to the value returned
--     in the @maxImageCount@ member of the
--     'Vulkan.Extensions.VK_KHR_surface.SurfaceCapabilitiesKHR' structure
--     returned by
--     'Vulkan.Extensions.VK_KHR_surface.getPhysicalDeviceSurfaceCapabilitiesKHR'
--     for the surface if the returned @maxImageCount@ is not zero
--
-- -   If @presentMode@ is not
--     'Vulkan.Extensions.VK_KHR_surface.PRESENT_MODE_SHARED_DEMAND_REFRESH_KHR'
--     nor
--     'Vulkan.Extensions.VK_KHR_surface.PRESENT_MODE_SHARED_CONTINUOUS_REFRESH_KHR',
--     then @minImageCount@ /must/ be greater than or equal to the value
--     returned in the @minImageCount@ member of the
--     'Vulkan.Extensions.VK_KHR_surface.SurfaceCapabilitiesKHR' structure
--     returned by
--     'Vulkan.Extensions.VK_KHR_surface.getPhysicalDeviceSurfaceCapabilitiesKHR'
--     for the surface
--
-- -   @minImageCount@ /must/ be @1@ if @presentMode@ is either
--     'Vulkan.Extensions.VK_KHR_surface.PRESENT_MODE_SHARED_DEMAND_REFRESH_KHR'
--     or
--     'Vulkan.Extensions.VK_KHR_surface.PRESENT_MODE_SHARED_CONTINUOUS_REFRESH_KHR'
--
-- -   @imageFormat@ and @imageColorSpace@ /must/ match the @format@ and
--     @colorSpace@ members, respectively, of one of the
--     'Vulkan.Extensions.VK_KHR_surface.SurfaceFormatKHR' structures
--     returned by
--     'Vulkan.Extensions.VK_KHR_surface.getPhysicalDeviceSurfaceFormatsKHR'
--     for the surface
--
-- -   @imageExtent@ /must/ be between @minImageExtent@ and
--     @maxImageExtent@, inclusive, where @minImageExtent@ and
--     @maxImageExtent@ are members of the
--     'Vulkan.Extensions.VK_KHR_surface.SurfaceCapabilitiesKHR' structure
--     returned by
--     'Vulkan.Extensions.VK_KHR_surface.getPhysicalDeviceSurfaceCapabilitiesKHR'
--     for the surface
--
-- -   @imageExtent@ members @width@ and @height@ /must/ both be non-zero
--
-- -   @imageArrayLayers@ /must/ be greater than @0@ and less than or equal
--     to the @maxImageArrayLayers@ member of the
--     'Vulkan.Extensions.VK_KHR_surface.SurfaceCapabilitiesKHR' structure
--     returned by
--     'Vulkan.Extensions.VK_KHR_surface.getPhysicalDeviceSurfaceCapabilitiesKHR'
--     for the surface
--
-- -   If @presentMode@ is
--     'Vulkan.Extensions.VK_KHR_surface.PRESENT_MODE_IMMEDIATE_KHR',
--     'Vulkan.Extensions.VK_KHR_surface.PRESENT_MODE_MAILBOX_KHR',
--     'Vulkan.Extensions.VK_KHR_surface.PRESENT_MODE_FIFO_KHR' or
--     'Vulkan.Extensions.VK_KHR_surface.PRESENT_MODE_FIFO_RELAXED_KHR',
--     @imageUsage@ /must/ be a subset of the supported usage flags present
--     in the @supportedUsageFlags@ member of the
--     'Vulkan.Extensions.VK_KHR_surface.SurfaceCapabilitiesKHR' structure
--     returned by
--     'Vulkan.Extensions.VK_KHR_surface.getPhysicalDeviceSurfaceCapabilitiesKHR'
--     for @surface@
--
-- -   If @presentMode@ is
--     'Vulkan.Extensions.VK_KHR_surface.PRESENT_MODE_SHARED_DEMAND_REFRESH_KHR'
--     or
--     'Vulkan.Extensions.VK_KHR_surface.PRESENT_MODE_SHARED_CONTINUOUS_REFRESH_KHR',
--     @imageUsage@ /must/ be a subset of the supported usage flags present
--     in the @sharedPresentSupportedUsageFlags@ member of the
--     'Vulkan.Extensions.VK_KHR_shared_presentable_image.SharedPresentSurfaceCapabilitiesKHR'
--     structure returned by
--     'Vulkan.Extensions.VK_KHR_get_surface_capabilities2.getPhysicalDeviceSurfaceCapabilities2KHR'
--     for @surface@
--
-- -   If @imageSharingMode@ is
--     'Vulkan.Core10.Enums.SharingMode.SHARING_MODE_CONCURRENT',
--     @pQueueFamilyIndices@ /must/ be a valid pointer to an array of
--     @queueFamilyIndexCount@ @uint32_t@ values
--
-- -   If @imageSharingMode@ is
--     'Vulkan.Core10.Enums.SharingMode.SHARING_MODE_CONCURRENT',
--     @queueFamilyIndexCount@ /must/ be greater than @1@
--
-- -   If @imageSharingMode@ is
--     'Vulkan.Core10.Enums.SharingMode.SHARING_MODE_CONCURRENT', each
--     element of @pQueueFamilyIndices@ /must/ be unique and /must/ be less
--     than @pQueueFamilyPropertyCount@ returned by either
--     'Vulkan.Core10.DeviceInitialization.getPhysicalDeviceQueueFamilyProperties'
--     or
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceQueueFamilyProperties2'
--     for the @physicalDevice@ that was used to create @device@
--
-- -   @preTransform@ /must/ be one of the bits present in the
--     @supportedTransforms@ member of the
--     'Vulkan.Extensions.VK_KHR_surface.SurfaceCapabilitiesKHR' structure
--     returned by
--     'Vulkan.Extensions.VK_KHR_surface.getPhysicalDeviceSurfaceCapabilitiesKHR'
--     for the surface
--
-- -   @compositeAlpha@ /must/ be one of the bits present in the
--     @supportedCompositeAlpha@ member of the
--     'Vulkan.Extensions.VK_KHR_surface.SurfaceCapabilitiesKHR' structure
--     returned by
--     'Vulkan.Extensions.VK_KHR_surface.getPhysicalDeviceSurfaceCapabilitiesKHR'
--     for the surface
--
-- -   @presentMode@ /must/ be one of the
--     'Vulkan.Extensions.VK_KHR_surface.PresentModeKHR' values returned by
--     'Vulkan.Extensions.VK_KHR_surface.getPhysicalDeviceSurfacePresentModesKHR'
--     for the surface
--
-- -   If the logical device was created with
--     'Vulkan.Core11.Promoted_From_VK_KHR_device_group_creation.DeviceGroupDeviceCreateInfo'::@physicalDeviceCount@
--     equal to 1, @flags@ /must/ not contain
--     'SWAPCHAIN_CREATE_SPLIT_INSTANCE_BIND_REGIONS_BIT_KHR'
--
-- -   If @oldSwapchain@ is not 'Vulkan.Core10.APIConstants.NULL_HANDLE',
--     @oldSwapchain@ /must/ be a non-retired swapchain associated with
--     native window referred to by @surface@
--
-- -   The
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#swapchain-wsi-image-create-info implied image creation parameters>
--     of the swapchain /must/ be supported as reported by
--     'Vulkan.Core10.DeviceInitialization.getPhysicalDeviceImageFormatProperties'
--
-- -   If @flags@ contains 'SWAPCHAIN_CREATE_MUTABLE_FORMAT_BIT_KHR' then
--     the @pNext@ chain /must/ include a
--     'Vulkan.Core12.Promoted_From_VK_KHR_image_format_list.ImageFormatListCreateInfo'
--     structure with a @viewFormatCount@ greater than zero and
--     @pViewFormats@ /must/ have an element equal to @imageFormat@
--
-- -   If a
--     'Vulkan.Core12.Promoted_From_VK_KHR_image_format_list.ImageFormatListCreateInfo'
--     structure was included in the @pNext@ chain and
--     'Vulkan.Core12.Promoted_From_VK_KHR_image_format_list.ImageFormatListCreateInfo'::@viewFormatCount@
--     is not zero then all of the formats in
--     'Vulkan.Core12.Promoted_From_VK_KHR_image_format_list.ImageFormatListCreateInfo'::@pViewFormats@
--     /must/ be compatible with the @format@ as described in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-compatibility compatibility table>
--
-- -   If @flags@ dose not contain
--     'SWAPCHAIN_CREATE_MUTABLE_FORMAT_BIT_KHR' and the @pNext@ chain
--     include a
--     'Vulkan.Core12.Promoted_From_VK_KHR_image_format_list.ImageFormatListCreateInfo'
--     structure then
--     'Vulkan.Core12.Promoted_From_VK_KHR_image_format_list.ImageFormatListCreateInfo'::@viewFormatCount@
--     /must/ be @0@ or @1@
--
-- -   If @flags@ contains 'SWAPCHAIN_CREATE_PROTECTED_BIT_KHR', then
--     'Vulkan.Extensions.VK_KHR_surface_protected_capabilities.SurfaceProtectedCapabilitiesKHR'::@supportsProtected@
--     /must/ be 'Vulkan.Core10.FundamentalTypes.TRUE' in the
--     'Vulkan.Extensions.VK_KHR_surface_protected_capabilities.SurfaceProtectedCapabilitiesKHR'
--     structure returned by
--     'Vulkan.Extensions.VK_KHR_get_surface_capabilities2.getPhysicalDeviceSurfaceCapabilities2KHR'
--     for @surface@
--
-- -   If the @pNext@ chain includes a
--     'Vulkan.Extensions.VK_EXT_full_screen_exclusive.SurfaceFullScreenExclusiveInfoEXT'
--     structure with its @fullScreenExclusive@ member set to
--     'Vulkan.Extensions.VK_EXT_full_screen_exclusive.FULL_SCREEN_EXCLUSIVE_APPLICATION_CONTROLLED_EXT',
--     and @surface@ was created using
--     'Vulkan.Extensions.VK_KHR_win32_surface.createWin32SurfaceKHR', a
--     'Vulkan.Extensions.VK_EXT_full_screen_exclusive.SurfaceFullScreenExclusiveWin32InfoEXT'
--     structure /must/ be included in the @pNext@ chain
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_SWAPCHAIN_CREATE_INFO_KHR'
--
-- -   Each @pNext@ member of any structure (including this one) in the
--     @pNext@ chain /must/ be either @NULL@ or a pointer to a valid
--     instance of 'DeviceGroupSwapchainCreateInfoKHR',
--     'Vulkan.Core12.Promoted_From_VK_KHR_image_format_list.ImageFormatListCreateInfo',
--     'Vulkan.Extensions.VK_EXT_full_screen_exclusive.SurfaceFullScreenExclusiveInfoEXT',
--     'Vulkan.Extensions.VK_EXT_full_screen_exclusive.SurfaceFullScreenExclusiveWin32InfoEXT',
--     'Vulkan.Extensions.VK_EXT_display_control.SwapchainCounterCreateInfoEXT',
--     or
--     'Vulkan.Extensions.VK_AMD_display_native_hdr.SwapchainDisplayNativeHdrCreateInfoAMD'
--
-- -   The @sType@ value of each struct in the @pNext@ chain /must/ be
--     unique
--
-- -   @flags@ /must/ be a valid combination of
--     'SwapchainCreateFlagBitsKHR' values
--
-- -   @surface@ /must/ be a valid 'Vulkan.Extensions.Handles.SurfaceKHR'
--     handle
--
-- -   @imageFormat@ /must/ be a valid 'Vulkan.Core10.Enums.Format.Format'
--     value
--
-- -   @imageColorSpace@ /must/ be a valid
--     'Vulkan.Extensions.VK_KHR_surface.ColorSpaceKHR' value
--
-- -   @imageUsage@ /must/ be a valid combination of
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.ImageUsageFlagBits' values
--
-- -   @imageUsage@ /must/ not be @0@
--
-- -   @imageSharingMode@ /must/ be a valid
--     'Vulkan.Core10.Enums.SharingMode.SharingMode' value
--
-- -   @preTransform@ /must/ be a valid
--     'Vulkan.Extensions.VK_KHR_surface.SurfaceTransformFlagBitsKHR' value
--
-- -   @compositeAlpha@ /must/ be a valid
--     'Vulkan.Extensions.VK_KHR_surface.CompositeAlphaFlagBitsKHR' value
--
-- -   @presentMode@ /must/ be a valid
--     'Vulkan.Extensions.VK_KHR_surface.PresentModeKHR' value
--
-- -   If @oldSwapchain@ is not 'Vulkan.Core10.APIConstants.NULL_HANDLE',
--     @oldSwapchain@ /must/ be a valid
--     'Vulkan.Extensions.Handles.SwapchainKHR' handle
--
-- -   If @oldSwapchain@ is a valid handle, it /must/ have been created,
--     allocated, or retrieved from @surface@
--
-- -   Both of @oldSwapchain@, and @surface@ that are valid handles of
--     non-ignored parameters /must/ have been created, allocated, or
--     retrieved from the same 'Vulkan.Core10.Handles.Instance'
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Extensions.VK_KHR_surface.ColorSpaceKHR',
-- 'Vulkan.Extensions.VK_KHR_surface.CompositeAlphaFlagBitsKHR',
-- 'Vulkan.Core10.FundamentalTypes.Extent2D',
-- 'Vulkan.Core10.Enums.Format.Format',
-- 'Vulkan.Core10.Enums.ImageUsageFlagBits.ImageUsageFlags',
-- 'Vulkan.Extensions.VK_KHR_surface.PresentModeKHR',
-- 'Vulkan.Core10.Enums.SharingMode.SharingMode',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'Vulkan.Extensions.Handles.SurfaceKHR',
-- 'Vulkan.Extensions.VK_KHR_surface.SurfaceTransformFlagBitsKHR',
-- 'SwapchainCreateFlagsKHR', 'Vulkan.Extensions.Handles.SwapchainKHR',
-- 'Vulkan.Extensions.VK_KHR_display_swapchain.createSharedSwapchainsKHR',
-- 'createSwapchainKHR'
data SwapchainCreateInfoKHR (es :: [Type]) = SwapchainCreateInfoKHR
  { -- | @pNext@ is @NULL@ or a pointer to a structure extending this structure.
    SwapchainCreateInfoKHR es -> Chain es
next :: Chain es
  , -- | @flags@ is a bitmask of 'SwapchainCreateFlagBitsKHR' indicating
    -- parameters of the swapchain creation.
    SwapchainCreateInfoKHR es -> SwapchainCreateFlagsKHR
flags :: SwapchainCreateFlagsKHR
  , -- | @surface@ is the surface onto which the swapchain will present images.
    -- If the creation succeeds, the swapchain becomes associated with
    -- @surface@.
    SwapchainCreateInfoKHR es -> SurfaceKHR
surface :: SurfaceKHR
  , -- | @minImageCount@ is the minimum number of presentable images that the
    -- application needs. The implementation will either create the swapchain
    -- with at least that many images, or it will fail to create the swapchain.
    SwapchainCreateInfoKHR es -> Word32
minImageCount :: Word32
  , -- | @imageFormat@ is a 'Vulkan.Core10.Enums.Format.Format' value specifying
    -- the format the swapchain image(s) will be created with.
    SwapchainCreateInfoKHR es -> Format
imageFormat :: Format
  , -- | @imageColorSpace@ is a 'Vulkan.Extensions.VK_KHR_surface.ColorSpaceKHR'
    -- value specifying the way the swapchain interprets image data.
    SwapchainCreateInfoKHR es -> ColorSpaceKHR
imageColorSpace :: ColorSpaceKHR
  , -- | @imageExtent@ is the size (in pixels) of the swapchain image(s). The
    -- behavior is platform-dependent if the image extent does not match the
    -- surface’s @currentExtent@ as returned by
    -- 'Vulkan.Extensions.VK_KHR_surface.getPhysicalDeviceSurfaceCapabilitiesKHR'.
    SwapchainCreateInfoKHR es -> Extent2D
imageExtent :: Extent2D
  , -- No documentation found for Nested "VkSwapchainCreateInfoKHR" "imageArrayLayers"
    SwapchainCreateInfoKHR es -> Word32
imageArrayLayers :: Word32
  , -- No documentation found for Nested "VkSwapchainCreateInfoKHR" "imageUsage"
    SwapchainCreateInfoKHR es -> ImageUsageFlags
imageUsage :: ImageUsageFlags
  , -- No documentation found for Nested "VkSwapchainCreateInfoKHR" "imageSharingMode"
    SwapchainCreateInfoKHR es -> SharingMode
imageSharingMode :: SharingMode
  , -- No documentation found for Nested "VkSwapchainCreateInfoKHR" "pQueueFamilyIndices"
    SwapchainCreateInfoKHR es -> Vector Word32
queueFamilyIndices :: Vector Word32
  , -- No documentation found for Nested "VkSwapchainCreateInfoKHR" "preTransform"
    SwapchainCreateInfoKHR es -> SurfaceTransformFlagBitsKHR
preTransform :: SurfaceTransformFlagBitsKHR
  , -- No documentation found for Nested "VkSwapchainCreateInfoKHR" "compositeAlpha"
    SwapchainCreateInfoKHR es -> CompositeAlphaFlagBitsKHR
compositeAlpha :: CompositeAlphaFlagBitsKHR
  , -- No documentation found for Nested "VkSwapchainCreateInfoKHR" "presentMode"
    SwapchainCreateInfoKHR es -> PresentModeKHR
presentMode :: PresentModeKHR
  , -- No documentation found for Nested "VkSwapchainCreateInfoKHR" "clipped"
    SwapchainCreateInfoKHR es -> Bool
clipped :: Bool
  , -- No documentation found for Nested "VkSwapchainCreateInfoKHR" "oldSwapchain"
    SwapchainCreateInfoKHR es -> SwapchainKHR
oldSwapchain :: SwapchainKHR
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (SwapchainCreateInfoKHR (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (SwapchainCreateInfoKHR es)

instance Extensible SwapchainCreateInfoKHR where
  extensibleType :: StructureType
extensibleType = StructureType
STRUCTURE_TYPE_SWAPCHAIN_CREATE_INFO_KHR
  setNext :: SwapchainCreateInfoKHR ds -> Chain es -> SwapchainCreateInfoKHR es
setNext x :: SwapchainCreateInfoKHR ds
x next :: Chain es
next = SwapchainCreateInfoKHR ds
x{$sel:next:SwapchainCreateInfoKHR :: Chain es
next = Chain es
next}
  getNext :: SwapchainCreateInfoKHR es -> Chain es
getNext SwapchainCreateInfoKHR{..} = Chain es
next
  extends :: forall e b proxy. Typeable e => proxy e -> (Extends SwapchainCreateInfoKHR e => b) -> Maybe b
  extends :: proxy e -> (Extends SwapchainCreateInfoKHR e => b) -> Maybe b
extends _ f :: Extends SwapchainCreateInfoKHR e => b
f
    | Just Refl <- (Typeable e, Typeable SurfaceFullScreenExclusiveWin32InfoEXT) =>
Maybe (e :~: SurfaceFullScreenExclusiveWin32InfoEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @SurfaceFullScreenExclusiveWin32InfoEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends SwapchainCreateInfoKHR e => b
f
    | Just Refl <- (Typeable e, Typeable SurfaceFullScreenExclusiveInfoEXT) =>
Maybe (e :~: SurfaceFullScreenExclusiveInfoEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @SurfaceFullScreenExclusiveInfoEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends SwapchainCreateInfoKHR e => b
f
    | Just Refl <- (Typeable e, Typeable ImageFormatListCreateInfo) =>
Maybe (e :~: ImageFormatListCreateInfo)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @ImageFormatListCreateInfo = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends SwapchainCreateInfoKHR e => b
f
    | Just Refl <- (Typeable e, Typeable SwapchainDisplayNativeHdrCreateInfoAMD) =>
Maybe (e :~: SwapchainDisplayNativeHdrCreateInfoAMD)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @SwapchainDisplayNativeHdrCreateInfoAMD = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends SwapchainCreateInfoKHR e => b
f
    | Just Refl <- (Typeable e, Typeable DeviceGroupSwapchainCreateInfoKHR) =>
Maybe (e :~: DeviceGroupSwapchainCreateInfoKHR)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @DeviceGroupSwapchainCreateInfoKHR = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends SwapchainCreateInfoKHR e => b
f
    | Just Refl <- (Typeable e, Typeable SwapchainCounterCreateInfoEXT) =>
Maybe (e :~: SwapchainCounterCreateInfoEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @SwapchainCounterCreateInfoEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends SwapchainCreateInfoKHR e => b
f
    | Bool
otherwise = Maybe b
forall a. Maybe a
Nothing

instance (Extendss SwapchainCreateInfoKHR es, PokeChain es) => ToCStruct (SwapchainCreateInfoKHR es) where
  withCStruct :: SwapchainCreateInfoKHR es
-> (Ptr (SwapchainCreateInfoKHR es) -> IO b) -> IO b
withCStruct x :: SwapchainCreateInfoKHR es
x f :: Ptr (SwapchainCreateInfoKHR es) -> IO b
f = Int -> Int -> (Ptr (SwapchainCreateInfoKHR es) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 104 8 ((Ptr (SwapchainCreateInfoKHR es) -> IO b) -> IO b)
-> (Ptr (SwapchainCreateInfoKHR es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr (SwapchainCreateInfoKHR es)
p -> Ptr (SwapchainCreateInfoKHR es)
-> SwapchainCreateInfoKHR es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (SwapchainCreateInfoKHR es)
p SwapchainCreateInfoKHR es
x (Ptr (SwapchainCreateInfoKHR es) -> IO b
f Ptr (SwapchainCreateInfoKHR es)
p)
  pokeCStruct :: Ptr (SwapchainCreateInfoKHR es)
-> SwapchainCreateInfoKHR es -> IO b -> IO b
pokeCStruct p :: Ptr (SwapchainCreateInfoKHR es)
p SwapchainCreateInfoKHR{..} f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SWAPCHAIN_CREATE_INFO_KHR)
    Ptr ()
pNext'' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ Chain es -> (Ptr (Chain es) -> IO b) -> IO b
forall (es :: [*]) a.
PokeChain es =>
Chain es -> (Ptr (Chain es) -> IO a) -> IO a
withChain (Chain es
next)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext''
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es)
-> Int -> Ptr SwapchainCreateFlagsKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr SwapchainCreateFlagsKHR)) (SwapchainCreateFlagsKHR
flags)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr SurfaceKHR -> SurfaceKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es) -> Int -> Ptr SurfaceKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr SurfaceKHR)) (SurfaceKHR
surface)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ ("pSwapchainImageCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es)
-> Int -> "pSwapchainImageCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word32)) (Word32
minImageCount)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Format -> Format -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es) -> Int -> Ptr Format
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr Format)) (Format
imageFormat)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ColorSpaceKHR -> ColorSpaceKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es) -> Int -> Ptr ColorSpaceKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr ColorSpaceKHR)) (ColorSpaceKHR
imageColorSpace)
    ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Extent2D -> Extent2D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es) -> Int -> Ptr Extent2D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Extent2D)) (Extent2D
imageExtent) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ ("pSwapchainImageCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es)
-> Int -> "pSwapchainImageCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 52 :: Ptr Word32)) (Word32
imageArrayLayers)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ImageUsageFlags -> ImageUsageFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es) -> Int -> Ptr ImageUsageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr ImageUsageFlags)) (ImageUsageFlags
imageUsage)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr SharingMode -> SharingMode -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es) -> Int -> Ptr SharingMode
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 60 :: Ptr SharingMode)) (SharingMode
imageSharingMode)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ ("pSwapchainImageCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es)
-> Int -> "pSwapchainImageCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr Word32)) ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector Word32 -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Word32 -> Int) -> Vector Word32 -> Int
forall a b. (a -> b) -> a -> b
$ (Vector Word32
queueFamilyIndices)) :: Word32))
    "pSwapchainImageCount" ::: Ptr Word32
pPQueueFamilyIndices' <- ((("pSwapchainImageCount" ::: Ptr Word32) -> IO b) -> IO b)
-> ContT b IO ("pSwapchainImageCount" ::: Ptr Word32)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pSwapchainImageCount" ::: Ptr Word32) -> IO b) -> IO b)
 -> ContT b IO ("pSwapchainImageCount" ::: Ptr Word32))
-> ((("pSwapchainImageCount" ::: Ptr Word32) -> IO b) -> IO b)
-> ContT b IO ("pSwapchainImageCount" ::: Ptr Word32)
forall a b. (a -> b) -> a -> b
$ Int
-> Int -> (("pSwapchainImageCount" ::: Ptr Word32) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Word32 ((Vector Word32 -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Word32
queueFamilyIndices)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 4) 4
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> Word32 -> IO ()) -> Vector Word32 -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Word32
e -> ("pSwapchainImageCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pSwapchainImageCount" ::: Ptr Word32
pPQueueFamilyIndices' ("pSwapchainImageCount" ::: Ptr Word32)
-> Int -> "pSwapchainImageCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32) (Word32
e)) (Vector Word32
queueFamilyIndices)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ("pSwapchainImageCount" ::: Ptr Word32)
-> ("pSwapchainImageCount" ::: Ptr Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es)
-> Int -> Ptr ("pSwapchainImageCount" ::: Ptr Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr (Ptr Word32))) ("pSwapchainImageCount" ::: Ptr Word32
pPQueueFamilyIndices')
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr SurfaceTransformFlagBitsKHR
-> SurfaceTransformFlagBitsKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es)
-> Int -> Ptr SurfaceTransformFlagBitsKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80 :: Ptr SurfaceTransformFlagBitsKHR)) (SurfaceTransformFlagBitsKHR
preTransform)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CompositeAlphaFlagBitsKHR -> CompositeAlphaFlagBitsKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es)
-> Int -> Ptr CompositeAlphaFlagBitsKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 84 :: Ptr CompositeAlphaFlagBitsKHR)) (CompositeAlphaFlagBitsKHR
compositeAlpha)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PresentModeKHR -> PresentModeKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es) -> Int -> Ptr PresentModeKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 88 :: Ptr PresentModeKHR)) (PresentModeKHR
presentMode)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 92 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
clipped))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ ("pSwapchain" ::: Ptr SwapchainKHR) -> SwapchainKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es)
-> Int -> "pSwapchain" ::: Ptr SwapchainKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 96 :: Ptr SwapchainKHR)) (SwapchainKHR
oldSwapchain)
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = 104
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr (SwapchainCreateInfoKHR es) -> IO b -> IO b
pokeZeroCStruct p :: Ptr (SwapchainCreateInfoKHR es)
p f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SWAPCHAIN_CREATE_INFO_KHR)
    Ptr ()
pNext' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ forall a. PokeChain es => (Ptr (Chain es) -> IO a) -> IO a
forall (es :: [*]) a.
PokeChain es =>
(Ptr (Chain es) -> IO a) -> IO a
withZeroChain @es
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext'
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr SurfaceKHR -> SurfaceKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es) -> Int -> Ptr SurfaceKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr SurfaceKHR)) (SurfaceKHR
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ ("pSwapchainImageCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es)
-> Int -> "pSwapchainImageCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Format -> Format -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es) -> Int -> Ptr Format
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr Format)) (Format
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ColorSpaceKHR -> ColorSpaceKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es) -> Int -> Ptr ColorSpaceKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr ColorSpaceKHR)) (ColorSpaceKHR
forall a. Zero a => a
zero)
    ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Extent2D -> Extent2D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es) -> Int -> Ptr Extent2D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Extent2D)) (Extent2D
forall a. Zero a => a
zero) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ ("pSwapchainImageCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es)
-> Int -> "pSwapchainImageCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 52 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ImageUsageFlags -> ImageUsageFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es) -> Int -> Ptr ImageUsageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr ImageUsageFlags)) (ImageUsageFlags
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr SharingMode -> SharingMode -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es) -> Int -> Ptr SharingMode
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 60 :: Ptr SharingMode)) (SharingMode
forall a. Zero a => a
zero)
    "pSwapchainImageCount" ::: Ptr Word32
pPQueueFamilyIndices' <- ((("pSwapchainImageCount" ::: Ptr Word32) -> IO b) -> IO b)
-> ContT b IO ("pSwapchainImageCount" ::: Ptr Word32)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pSwapchainImageCount" ::: Ptr Word32) -> IO b) -> IO b)
 -> ContT b IO ("pSwapchainImageCount" ::: Ptr Word32))
-> ((("pSwapchainImageCount" ::: Ptr Word32) -> IO b) -> IO b)
-> ContT b IO ("pSwapchainImageCount" ::: Ptr Word32)
forall a b. (a -> b) -> a -> b
$ Int
-> Int -> (("pSwapchainImageCount" ::: Ptr Word32) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Word32 ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 4) 4
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> Word32 -> IO ()) -> Vector Word32 -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Word32
e -> ("pSwapchainImageCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pSwapchainImageCount" ::: Ptr Word32
pPQueueFamilyIndices' ("pSwapchainImageCount" ::: Ptr Word32)
-> Int -> "pSwapchainImageCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32) (Word32
e)) (Vector Word32
forall a. Monoid a => a
mempty)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ("pSwapchainImageCount" ::: Ptr Word32)
-> ("pSwapchainImageCount" ::: Ptr Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es)
-> Int -> Ptr ("pSwapchainImageCount" ::: Ptr Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr (Ptr Word32))) ("pSwapchainImageCount" ::: Ptr Word32
pPQueueFamilyIndices')
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr SurfaceTransformFlagBitsKHR
-> SurfaceTransformFlagBitsKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es)
-> Int -> Ptr SurfaceTransformFlagBitsKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80 :: Ptr SurfaceTransformFlagBitsKHR)) (SurfaceTransformFlagBitsKHR
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CompositeAlphaFlagBitsKHR -> CompositeAlphaFlagBitsKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es)
-> Int -> Ptr CompositeAlphaFlagBitsKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 84 :: Ptr CompositeAlphaFlagBitsKHR)) (CompositeAlphaFlagBitsKHR
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PresentModeKHR -> PresentModeKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es) -> Int -> Ptr PresentModeKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 88 :: Ptr PresentModeKHR)) (PresentModeKHR
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 92 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f

instance (Extendss SwapchainCreateInfoKHR es, PeekChain es) => FromCStruct (SwapchainCreateInfoKHR es) where
  peekCStruct :: Ptr (SwapchainCreateInfoKHR es) -> IO (SwapchainCreateInfoKHR es)
peekCStruct p :: Ptr (SwapchainCreateInfoKHR es)
p = do
    Ptr ()
pNext <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ())))
    Chain es
next <- Ptr (Chain es) -> IO (Chain es)
forall (es :: [*]). PeekChain es => Ptr (Chain es) -> IO (Chain es)
peekChain (Ptr () -> Ptr (Chain es)
forall a b. Ptr a -> Ptr b
castPtr Ptr ()
pNext)
    SwapchainCreateFlagsKHR
flags <- Ptr SwapchainCreateFlagsKHR -> IO SwapchainCreateFlagsKHR
forall a. Storable a => Ptr a -> IO a
peek @SwapchainCreateFlagsKHR ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es)
-> Int -> Ptr SwapchainCreateFlagsKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr SwapchainCreateFlagsKHR))
    SurfaceKHR
surface <- Ptr SurfaceKHR -> IO SurfaceKHR
forall a. Storable a => Ptr a -> IO a
peek @SurfaceKHR ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es) -> Int -> Ptr SurfaceKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr SurfaceKHR))
    Word32
minImageCount <- ("pSwapchainImageCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es)
-> Int -> "pSwapchainImageCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word32))
    Format
imageFormat <- Ptr Format -> IO Format
forall a. Storable a => Ptr a -> IO a
peek @Format ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es) -> Int -> Ptr Format
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr Format))
    ColorSpaceKHR
imageColorSpace <- Ptr ColorSpaceKHR -> IO ColorSpaceKHR
forall a. Storable a => Ptr a -> IO a
peek @ColorSpaceKHR ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es) -> Int -> Ptr ColorSpaceKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr ColorSpaceKHR))
    Extent2D
imageExtent <- Ptr Extent2D -> IO Extent2D
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Extent2D ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es) -> Int -> Ptr Extent2D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Extent2D))
    Word32
imageArrayLayers <- ("pSwapchainImageCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es)
-> Int -> "pSwapchainImageCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 52 :: Ptr Word32))
    ImageUsageFlags
imageUsage <- Ptr ImageUsageFlags -> IO ImageUsageFlags
forall a. Storable a => Ptr a -> IO a
peek @ImageUsageFlags ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es) -> Int -> Ptr ImageUsageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr ImageUsageFlags))
    SharingMode
imageSharingMode <- Ptr SharingMode -> IO SharingMode
forall a. Storable a => Ptr a -> IO a
peek @SharingMode ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es) -> Int -> Ptr SharingMode
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 60 :: Ptr SharingMode))
    Word32
queueFamilyIndexCount <- ("pSwapchainImageCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es)
-> Int -> "pSwapchainImageCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr Word32))
    "pSwapchainImageCount" ::: Ptr Word32
pQueueFamilyIndices <- Ptr ("pSwapchainImageCount" ::: Ptr Word32)
-> IO ("pSwapchainImageCount" ::: Ptr Word32)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr Word32) ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es)
-> Int -> Ptr ("pSwapchainImageCount" ::: Ptr Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr (Ptr Word32)))
    Vector Word32
pQueueFamilyIndices' <- Int -> (Int -> IO Word32) -> IO (Vector Word32)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
queueFamilyIndexCount) (\i :: Int
i -> ("pSwapchainImageCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pSwapchainImageCount" ::: Ptr Word32
pQueueFamilyIndices ("pSwapchainImageCount" ::: Ptr Word32)
-> Int -> "pSwapchainImageCount" ::: Ptr Word32
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32)))
    SurfaceTransformFlagBitsKHR
preTransform <- Ptr SurfaceTransformFlagBitsKHR -> IO SurfaceTransformFlagBitsKHR
forall a. Storable a => Ptr a -> IO a
peek @SurfaceTransformFlagBitsKHR ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es)
-> Int -> Ptr SurfaceTransformFlagBitsKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80 :: Ptr SurfaceTransformFlagBitsKHR))
    CompositeAlphaFlagBitsKHR
compositeAlpha <- Ptr CompositeAlphaFlagBitsKHR -> IO CompositeAlphaFlagBitsKHR
forall a. Storable a => Ptr a -> IO a
peek @CompositeAlphaFlagBitsKHR ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es)
-> Int -> Ptr CompositeAlphaFlagBitsKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 84 :: Ptr CompositeAlphaFlagBitsKHR))
    PresentModeKHR
presentMode <- Ptr PresentModeKHR -> IO PresentModeKHR
forall a. Storable a => Ptr a -> IO a
peek @PresentModeKHR ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es) -> Int -> Ptr PresentModeKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 88 :: Ptr PresentModeKHR))
    Bool32
clipped <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 92 :: Ptr Bool32))
    SwapchainKHR
oldSwapchain <- ("pSwapchain" ::: Ptr SwapchainKHR) -> IO SwapchainKHR
forall a. Storable a => Ptr a -> IO a
peek @SwapchainKHR ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es)
-> Int -> "pSwapchain" ::: Ptr SwapchainKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 96 :: Ptr SwapchainKHR))
    SwapchainCreateInfoKHR es -> IO (SwapchainCreateInfoKHR es)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SwapchainCreateInfoKHR es -> IO (SwapchainCreateInfoKHR es))
-> SwapchainCreateInfoKHR es -> IO (SwapchainCreateInfoKHR es)
forall a b. (a -> b) -> a -> b
$ Chain es
-> SwapchainCreateFlagsKHR
-> SurfaceKHR
-> Word32
-> Format
-> ColorSpaceKHR
-> Extent2D
-> Word32
-> ImageUsageFlags
-> SharingMode
-> Vector Word32
-> SurfaceTransformFlagBitsKHR
-> CompositeAlphaFlagBitsKHR
-> PresentModeKHR
-> Bool
-> SwapchainKHR
-> SwapchainCreateInfoKHR es
forall (es :: [*]).
Chain es
-> SwapchainCreateFlagsKHR
-> SurfaceKHR
-> Word32
-> Format
-> ColorSpaceKHR
-> Extent2D
-> Word32
-> ImageUsageFlags
-> SharingMode
-> Vector Word32
-> SurfaceTransformFlagBitsKHR
-> CompositeAlphaFlagBitsKHR
-> PresentModeKHR
-> Bool
-> SwapchainKHR
-> SwapchainCreateInfoKHR es
SwapchainCreateInfoKHR
             Chain es
next SwapchainCreateFlagsKHR
flags SurfaceKHR
surface Word32
minImageCount Format
imageFormat ColorSpaceKHR
imageColorSpace Extent2D
imageExtent Word32
imageArrayLayers ImageUsageFlags
imageUsage SharingMode
imageSharingMode Vector Word32
pQueueFamilyIndices' SurfaceTransformFlagBitsKHR
preTransform CompositeAlphaFlagBitsKHR
compositeAlpha PresentModeKHR
presentMode (Bool32 -> Bool
bool32ToBool Bool32
clipped) SwapchainKHR
oldSwapchain

instance es ~ '[] => Zero (SwapchainCreateInfoKHR es) where
  zero :: SwapchainCreateInfoKHR es
zero = Chain es
-> SwapchainCreateFlagsKHR
-> SurfaceKHR
-> Word32
-> Format
-> ColorSpaceKHR
-> Extent2D
-> Word32
-> ImageUsageFlags
-> SharingMode
-> Vector Word32
-> SurfaceTransformFlagBitsKHR
-> CompositeAlphaFlagBitsKHR
-> PresentModeKHR
-> Bool
-> SwapchainKHR
-> SwapchainCreateInfoKHR es
forall (es :: [*]).
Chain es
-> SwapchainCreateFlagsKHR
-> SurfaceKHR
-> Word32
-> Format
-> ColorSpaceKHR
-> Extent2D
-> Word32
-> ImageUsageFlags
-> SharingMode
-> Vector Word32
-> SurfaceTransformFlagBitsKHR
-> CompositeAlphaFlagBitsKHR
-> PresentModeKHR
-> Bool
-> SwapchainKHR
-> SwapchainCreateInfoKHR es
SwapchainCreateInfoKHR
           ()
           SwapchainCreateFlagsKHR
forall a. Zero a => a
zero
           SurfaceKHR
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Format
forall a. Zero a => a
zero
           ColorSpaceKHR
forall a. Zero a => a
zero
           Extent2D
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           ImageUsageFlags
forall a. Zero a => a
zero
           SharingMode
forall a. Zero a => a
zero
           Vector Word32
forall a. Monoid a => a
mempty
           SurfaceTransformFlagBitsKHR
forall a. Zero a => a
zero
           CompositeAlphaFlagBitsKHR
forall a. Zero a => a
zero
           PresentModeKHR
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           SwapchainKHR
forall a. Zero a => a
zero


-- | VkPresentInfoKHR - Structure describing parameters of a queue
-- presentation
--
-- = Description
--
-- Before an application /can/ present an image, the image’s layout /must/
-- be transitioned to the
-- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_PRESENT_SRC_KHR' layout,
-- or for a shared presentable image the
-- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_SHARED_PRESENT_KHR'
-- layout.
--
-- Note
--
-- When transitioning the image to
-- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_SHARED_PRESENT_KHR' or
-- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_PRESENT_SRC_KHR', there is
-- no need to delay subsequent processing, or perform any visibility
-- operations (as 'queuePresentKHR' performs automatic visibility
-- operations). To achieve this, the @dstAccessMask@ member of the
-- 'Vulkan.Core10.OtherTypes.ImageMemoryBarrier' /should/ be set to @0@,
-- and the @dstStageMask@ parameter /should/ be set to
-- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_BOTTOM_OF_PIPE_BIT'.
--
-- == Valid Usage
--
-- -   Each element of @pImageIndices@ /must/ be the index of a presentable
--     image acquired from the swapchain specified by the corresponding
--     element of the @pSwapchains@ array, and the presented image
--     subresource /must/ be in the
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_PRESENT_SRC_KHR' or
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_SHARED_PRESENT_KHR'
--     layout at the time the operation is executed on a
--     'Vulkan.Core10.Handles.Device'
--
-- -   All elements of the @pWaitSemaphores@ /must/ have a
--     'Vulkan.Core12.Enums.SemaphoreType.SemaphoreType' of
--     'Vulkan.Core12.Enums.SemaphoreType.SEMAPHORE_TYPE_BINARY'
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PRESENT_INFO_KHR'
--
-- -   Each @pNext@ member of any structure (including this one) in the
--     @pNext@ chain /must/ be either @NULL@ or a pointer to a valid
--     instance of 'DeviceGroupPresentInfoKHR',
--     'Vulkan.Extensions.VK_KHR_display_swapchain.DisplayPresentInfoKHR',
--     'Vulkan.Extensions.VK_GGP_frame_token.PresentFrameTokenGGP',
--     'Vulkan.Extensions.VK_KHR_incremental_present.PresentRegionsKHR', or
--     'Vulkan.Extensions.VK_GOOGLE_display_timing.PresentTimesInfoGOOGLE'
--
-- -   The @sType@ value of each struct in the @pNext@ chain /must/ be
--     unique
--
-- -   If @waitSemaphoreCount@ is not @0@, @pWaitSemaphores@ /must/ be a
--     valid pointer to an array of @waitSemaphoreCount@ valid
--     'Vulkan.Core10.Handles.Semaphore' handles
--
-- -   @pSwapchains@ /must/ be a valid pointer to an array of
--     @swapchainCount@ valid 'Vulkan.Extensions.Handles.SwapchainKHR'
--     handles
--
-- -   @pImageIndices@ /must/ be a valid pointer to an array of
--     @swapchainCount@ @uint32_t@ values
--
-- -   If @pResults@ is not @NULL@, @pResults@ /must/ be a valid pointer to
--     an array of @swapchainCount@ 'Vulkan.Core10.Enums.Result.Result'
--     values
--
-- -   @swapchainCount@ /must/ be greater than @0@
--
-- -   Both of the elements of @pSwapchains@, and the elements of
--     @pWaitSemaphores@ that are valid handles of non-ignored parameters
--     /must/ have been created, allocated, or retrieved from the same
--     'Vulkan.Core10.Handles.Instance'
--
-- = See Also
--
-- 'Vulkan.Core10.Enums.Result.Result', 'Vulkan.Core10.Handles.Semaphore',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'Vulkan.Extensions.Handles.SwapchainKHR', 'queuePresentKHR'
data PresentInfoKHR (es :: [Type]) = PresentInfoKHR
  { -- | @pNext@ is @NULL@ or a pointer to a structure extending this structure.
    PresentInfoKHR es -> Chain es
next :: Chain es
  , -- | @pWaitSemaphores@ is @NULL@ or a pointer to an array of
    -- 'Vulkan.Core10.Handles.Semaphore' objects with @waitSemaphoreCount@
    -- entries, and specifies the semaphores to wait for before issuing the
    -- present request.
    PresentInfoKHR es -> Vector Semaphore
waitSemaphores :: Vector Semaphore
  , -- | @pSwapchains@ is a pointer to an array of
    -- 'Vulkan.Extensions.Handles.SwapchainKHR' objects with @swapchainCount@
    -- entries. A given swapchain /must/ not appear in this list more than
    -- once.
    PresentInfoKHR es -> Vector SwapchainKHR
swapchains :: Vector SwapchainKHR
  , -- | @pImageIndices@ is a pointer to an array of indices into the array of
    -- each swapchain’s presentable images, with @swapchainCount@ entries. Each
    -- entry in this array identifies the image to present on the corresponding
    -- entry in the @pSwapchains@ array.
    PresentInfoKHR es -> Vector Word32
imageIndices :: Vector Word32
  , -- | @pResults@ is a pointer to an array of
    -- 'Vulkan.Core10.Enums.Result.Result' typed elements with @swapchainCount@
    -- entries. Applications that do not need per-swapchain results /can/ use
    -- @NULL@ for @pResults@. If non-@NULL@, each entry in @pResults@ will be
    -- set to the 'Vulkan.Core10.Enums.Result.Result' for presenting the
    -- swapchain corresponding to the same index in @pSwapchains@.
    PresentInfoKHR es -> Ptr Result
results :: Ptr Result
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PresentInfoKHR (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (PresentInfoKHR es)

instance Extensible PresentInfoKHR where
  extensibleType :: StructureType
extensibleType = StructureType
STRUCTURE_TYPE_PRESENT_INFO_KHR
  setNext :: PresentInfoKHR ds -> Chain es -> PresentInfoKHR es
setNext x :: PresentInfoKHR ds
x next :: Chain es
next = PresentInfoKHR ds
x{$sel:next:PresentInfoKHR :: Chain es
next = Chain es
next}
  getNext :: PresentInfoKHR es -> Chain es
getNext PresentInfoKHR{..} = Chain es
next
  extends :: forall e b proxy. Typeable e => proxy e -> (Extends PresentInfoKHR e => b) -> Maybe b
  extends :: proxy e -> (Extends PresentInfoKHR e => b) -> Maybe b
extends _ f :: Extends PresentInfoKHR e => b
f
    | Just Refl <- (Typeable e, Typeable PresentFrameTokenGGP) =>
Maybe (e :~: PresentFrameTokenGGP)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PresentFrameTokenGGP = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PresentInfoKHR e => b
f
    | Just Refl <- (Typeable e, Typeable PresentTimesInfoGOOGLE) =>
Maybe (e :~: PresentTimesInfoGOOGLE)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PresentTimesInfoGOOGLE = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PresentInfoKHR e => b
f
    | Just Refl <- (Typeable e, Typeable DeviceGroupPresentInfoKHR) =>
Maybe (e :~: DeviceGroupPresentInfoKHR)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @DeviceGroupPresentInfoKHR = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PresentInfoKHR e => b
f
    | Just Refl <- (Typeable e, Typeable PresentRegionsKHR) =>
Maybe (e :~: PresentRegionsKHR)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PresentRegionsKHR = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PresentInfoKHR e => b
f
    | Just Refl <- (Typeable e, Typeable DisplayPresentInfoKHR) =>
Maybe (e :~: DisplayPresentInfoKHR)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @DisplayPresentInfoKHR = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PresentInfoKHR e => b
f
    | Bool
otherwise = Maybe b
forall a. Maybe a
Nothing

instance (Extendss PresentInfoKHR es, PokeChain es) => ToCStruct (PresentInfoKHR es) where
  withCStruct :: PresentInfoKHR es -> (Ptr (PresentInfoKHR es) -> IO b) -> IO b
withCStruct x :: PresentInfoKHR es
x f :: Ptr (PresentInfoKHR es) -> IO b
f = Int -> Int -> (Ptr (PresentInfoKHR es) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 64 8 ((Ptr (PresentInfoKHR es) -> IO b) -> IO b)
-> (Ptr (PresentInfoKHR es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr (PresentInfoKHR es)
p -> Ptr (PresentInfoKHR es) -> PresentInfoKHR es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (PresentInfoKHR es)
p PresentInfoKHR es
x (Ptr (PresentInfoKHR es) -> IO b
f Ptr (PresentInfoKHR es)
p)
  pokeCStruct :: Ptr (PresentInfoKHR es) -> PresentInfoKHR es -> IO b -> IO b
pokeCStruct p :: Ptr (PresentInfoKHR es)
p PresentInfoKHR{..} f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PresentInfoKHR es)
p Ptr (PresentInfoKHR es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PRESENT_INFO_KHR)
    Ptr ()
pNext'' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ Chain es -> (Ptr (Chain es) -> IO b) -> IO b
forall (es :: [*]) a.
PokeChain es =>
Chain es -> (Ptr (Chain es) -> IO a) -> IO a
withChain (Chain es
next)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PresentInfoKHR es)
p Ptr (PresentInfoKHR es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext''
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ ("pSwapchainImageCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PresentInfoKHR es)
p Ptr (PresentInfoKHR es)
-> Int -> "pSwapchainImageCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector Semaphore -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Semaphore -> Int) -> Vector Semaphore -> Int
forall a b. (a -> b) -> a -> b
$ (Vector Semaphore
waitSemaphores)) :: Word32))
    Ptr Semaphore
pPWaitSemaphores' <- ((Ptr Semaphore -> IO b) -> IO b) -> ContT b IO (Ptr Semaphore)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Semaphore -> IO b) -> IO b) -> ContT b IO (Ptr Semaphore))
-> ((Ptr Semaphore -> IO b) -> IO b) -> ContT b IO (Ptr Semaphore)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr Semaphore -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Semaphore ((Vector Semaphore -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Semaphore
waitSemaphores)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 8
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> Semaphore -> IO ()) -> Vector Semaphore -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Semaphore
e -> Ptr Semaphore -> Semaphore -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Semaphore
pPWaitSemaphores' Ptr Semaphore -> Int -> Ptr Semaphore
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Semaphore) (Semaphore
e)) (Vector Semaphore
waitSemaphores)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr Semaphore) -> Ptr Semaphore -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PresentInfoKHR es)
p Ptr (PresentInfoKHR es) -> Int -> Ptr (Ptr Semaphore)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr Semaphore))) (Ptr Semaphore
pPWaitSemaphores')
    let pSwapchainsLength :: Int
pSwapchainsLength = Vector SwapchainKHR -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector SwapchainKHR -> Int) -> Vector SwapchainKHR -> Int
forall a b. (a -> b) -> a -> b
$ (Vector SwapchainKHR
swapchains)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ((Vector Word32 -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Word32 -> Int) -> Vector Word32 -> Int
forall a b. (a -> b) -> a -> b
$ (Vector Word32
imageIndices)) Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
pSwapchainsLength) (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 "" "pImageIndices and pSwapchains must have the same length" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ ("pSwapchainImageCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PresentInfoKHR es)
p Ptr (PresentInfoKHR es)
-> Int -> "pSwapchainImageCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word32)) ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
pSwapchainsLength :: Word32))
    "pSwapchain" ::: Ptr SwapchainKHR
pPSwapchains' <- ((("pSwapchain" ::: Ptr SwapchainKHR) -> IO b) -> IO b)
-> ContT b IO ("pSwapchain" ::: Ptr SwapchainKHR)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pSwapchain" ::: Ptr SwapchainKHR) -> IO b) -> IO b)
 -> ContT b IO ("pSwapchain" ::: Ptr SwapchainKHR))
-> ((("pSwapchain" ::: Ptr SwapchainKHR) -> IO b) -> IO b)
-> ContT b IO ("pSwapchain" ::: Ptr SwapchainKHR)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (("pSwapchain" ::: Ptr SwapchainKHR) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @SwapchainKHR ((Vector SwapchainKHR -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector SwapchainKHR
swapchains)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 8
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> SwapchainKHR -> IO ()) -> Vector SwapchainKHR -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SwapchainKHR
e -> ("pSwapchain" ::: Ptr SwapchainKHR) -> SwapchainKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pSwapchain" ::: Ptr SwapchainKHR
pPSwapchains' ("pSwapchain" ::: Ptr SwapchainKHR)
-> Int -> "pSwapchain" ::: Ptr SwapchainKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SwapchainKHR) (SwapchainKHR
e)) (Vector SwapchainKHR
swapchains)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ("pSwapchain" ::: Ptr SwapchainKHR)
-> ("pSwapchain" ::: Ptr SwapchainKHR) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PresentInfoKHR es)
p Ptr (PresentInfoKHR es)
-> Int -> Ptr ("pSwapchain" ::: Ptr SwapchainKHR)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr SwapchainKHR))) ("pSwapchain" ::: Ptr SwapchainKHR
pPSwapchains')
    "pSwapchainImageCount" ::: Ptr Word32
pPImageIndices' <- ((("pSwapchainImageCount" ::: Ptr Word32) -> IO b) -> IO b)
-> ContT b IO ("pSwapchainImageCount" ::: Ptr Word32)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pSwapchainImageCount" ::: Ptr Word32) -> IO b) -> IO b)
 -> ContT b IO ("pSwapchainImageCount" ::: Ptr Word32))
-> ((("pSwapchainImageCount" ::: Ptr Word32) -> IO b) -> IO b)
-> ContT b IO ("pSwapchainImageCount" ::: Ptr Word32)
forall a b. (a -> b) -> a -> b
$ Int
-> Int -> (("pSwapchainImageCount" ::: Ptr Word32) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Word32 ((Vector Word32 -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Word32
imageIndices)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 4) 4
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> Word32 -> IO ()) -> Vector Word32 -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Word32
e -> ("pSwapchainImageCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pSwapchainImageCount" ::: Ptr Word32
pPImageIndices' ("pSwapchainImageCount" ::: Ptr Word32)
-> Int -> "pSwapchainImageCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32) (Word32
e)) (Vector Word32
imageIndices)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ("pSwapchainImageCount" ::: Ptr Word32)
-> ("pSwapchainImageCount" ::: Ptr Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PresentInfoKHR es)
p Ptr (PresentInfoKHR es)
-> Int -> Ptr ("pSwapchainImageCount" ::: Ptr Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr (Ptr Word32))) ("pSwapchainImageCount" ::: Ptr Word32
pPImageIndices')
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr Result) -> Ptr Result -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PresentInfoKHR es)
p Ptr (PresentInfoKHR es) -> Int -> Ptr (Ptr Result)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr (Ptr Result))) (Ptr Result
results)
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = 64
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr (PresentInfoKHR es) -> IO b -> IO b
pokeZeroCStruct p :: Ptr (PresentInfoKHR es)
p f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PresentInfoKHR es)
p Ptr (PresentInfoKHR es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PRESENT_INFO_KHR)
    Ptr ()
pNext' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ forall a. PokeChain es => (Ptr (Chain es) -> IO a) -> IO a
forall (es :: [*]) a.
PokeChain es =>
(Ptr (Chain es) -> IO a) -> IO a
withZeroChain @es
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PresentInfoKHR es)
p Ptr (PresentInfoKHR es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext'
    Ptr Semaphore
pPWaitSemaphores' <- ((Ptr Semaphore -> IO b) -> IO b) -> ContT b IO (Ptr Semaphore)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Semaphore -> IO b) -> IO b) -> ContT b IO (Ptr Semaphore))
-> ((Ptr Semaphore -> IO b) -> IO b) -> ContT b IO (Ptr Semaphore)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr Semaphore -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Semaphore ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 8
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> Semaphore -> IO ()) -> Vector Semaphore -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Semaphore
e -> Ptr Semaphore -> Semaphore -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Semaphore
pPWaitSemaphores' Ptr Semaphore -> Int -> Ptr Semaphore
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Semaphore) (Semaphore
e)) (Vector Semaphore
forall a. Monoid a => a
mempty)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr Semaphore) -> Ptr Semaphore -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PresentInfoKHR es)
p Ptr (PresentInfoKHR es) -> Int -> Ptr (Ptr Semaphore)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr Semaphore))) (Ptr Semaphore
pPWaitSemaphores')
    "pSwapchain" ::: Ptr SwapchainKHR
pPSwapchains' <- ((("pSwapchain" ::: Ptr SwapchainKHR) -> IO b) -> IO b)
-> ContT b IO ("pSwapchain" ::: Ptr SwapchainKHR)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pSwapchain" ::: Ptr SwapchainKHR) -> IO b) -> IO b)
 -> ContT b IO ("pSwapchain" ::: Ptr SwapchainKHR))
-> ((("pSwapchain" ::: Ptr SwapchainKHR) -> IO b) -> IO b)
-> ContT b IO ("pSwapchain" ::: Ptr SwapchainKHR)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (("pSwapchain" ::: Ptr SwapchainKHR) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @SwapchainKHR ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 8
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> SwapchainKHR -> IO ()) -> Vector SwapchainKHR -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SwapchainKHR
e -> ("pSwapchain" ::: Ptr SwapchainKHR) -> SwapchainKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pSwapchain" ::: Ptr SwapchainKHR
pPSwapchains' ("pSwapchain" ::: Ptr SwapchainKHR)
-> Int -> "pSwapchain" ::: Ptr SwapchainKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SwapchainKHR) (SwapchainKHR
e)) (Vector SwapchainKHR
forall a. Monoid a => a
mempty)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ("pSwapchain" ::: Ptr SwapchainKHR)
-> ("pSwapchain" ::: Ptr SwapchainKHR) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PresentInfoKHR es)
p Ptr (PresentInfoKHR es)
-> Int -> Ptr ("pSwapchain" ::: Ptr SwapchainKHR)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr SwapchainKHR))) ("pSwapchain" ::: Ptr SwapchainKHR
pPSwapchains')
    "pSwapchainImageCount" ::: Ptr Word32
pPImageIndices' <- ((("pSwapchainImageCount" ::: Ptr Word32) -> IO b) -> IO b)
-> ContT b IO ("pSwapchainImageCount" ::: Ptr Word32)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pSwapchainImageCount" ::: Ptr Word32) -> IO b) -> IO b)
 -> ContT b IO ("pSwapchainImageCount" ::: Ptr Word32))
-> ((("pSwapchainImageCount" ::: Ptr Word32) -> IO b) -> IO b)
-> ContT b IO ("pSwapchainImageCount" ::: Ptr Word32)
forall a b. (a -> b) -> a -> b
$ Int
-> Int -> (("pSwapchainImageCount" ::: Ptr Word32) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Word32 ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 4) 4
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> Word32 -> IO ()) -> Vector Word32 -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Word32
e -> ("pSwapchainImageCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pSwapchainImageCount" ::: Ptr Word32
pPImageIndices' ("pSwapchainImageCount" ::: Ptr Word32)
-> Int -> "pSwapchainImageCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32) (Word32
e)) (Vector Word32
forall a. Monoid a => a
mempty)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ("pSwapchainImageCount" ::: Ptr Word32)
-> ("pSwapchainImageCount" ::: Ptr Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PresentInfoKHR es)
p Ptr (PresentInfoKHR es)
-> Int -> Ptr ("pSwapchainImageCount" ::: Ptr Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr (Ptr Word32))) ("pSwapchainImageCount" ::: Ptr Word32
pPImageIndices')
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f

instance (Extendss PresentInfoKHR es, PeekChain es) => FromCStruct (PresentInfoKHR es) where
  peekCStruct :: Ptr (PresentInfoKHR es) -> IO (PresentInfoKHR es)
peekCStruct p :: Ptr (PresentInfoKHR es)
p = do
    Ptr ()
pNext <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (PresentInfoKHR es)
p Ptr (PresentInfoKHR es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ())))
    Chain es
next <- Ptr (Chain es) -> IO (Chain es)
forall (es :: [*]). PeekChain es => Ptr (Chain es) -> IO (Chain es)
peekChain (Ptr () -> Ptr (Chain es)
forall a b. Ptr a -> Ptr b
castPtr Ptr ()
pNext)
    Word32
waitSemaphoreCount <- ("pSwapchainImageCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (PresentInfoKHR es)
p Ptr (PresentInfoKHR es)
-> Int -> "pSwapchainImageCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32))
    Ptr Semaphore
pWaitSemaphores <- Ptr (Ptr Semaphore) -> IO (Ptr Semaphore)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr Semaphore) ((Ptr (PresentInfoKHR es)
p Ptr (PresentInfoKHR es) -> Int -> Ptr (Ptr Semaphore)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr Semaphore)))
    Vector Semaphore
pWaitSemaphores' <- Int -> (Int -> IO Semaphore) -> IO (Vector Semaphore)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
waitSemaphoreCount) (\i :: Int
i -> Ptr Semaphore -> IO Semaphore
forall a. Storable a => Ptr a -> IO a
peek @Semaphore ((Ptr Semaphore
pWaitSemaphores Ptr Semaphore -> Int -> Ptr Semaphore
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Semaphore)))
    Word32
swapchainCount <- ("pSwapchainImageCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (PresentInfoKHR es)
p Ptr (PresentInfoKHR es)
-> Int -> "pSwapchainImageCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word32))
    "pSwapchain" ::: Ptr SwapchainKHR
pSwapchains <- Ptr ("pSwapchain" ::: Ptr SwapchainKHR)
-> IO ("pSwapchain" ::: Ptr SwapchainKHR)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr SwapchainKHR) ((Ptr (PresentInfoKHR es)
p Ptr (PresentInfoKHR es)
-> Int -> Ptr ("pSwapchain" ::: Ptr SwapchainKHR)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr SwapchainKHR)))
    Vector SwapchainKHR
pSwapchains' <- Int -> (Int -> IO SwapchainKHR) -> IO (Vector SwapchainKHR)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
swapchainCount) (\i :: Int
i -> ("pSwapchain" ::: Ptr SwapchainKHR) -> IO SwapchainKHR
forall a. Storable a => Ptr a -> IO a
peek @SwapchainKHR (("pSwapchain" ::: Ptr SwapchainKHR
pSwapchains ("pSwapchain" ::: Ptr SwapchainKHR)
-> Int -> "pSwapchain" ::: Ptr SwapchainKHR
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SwapchainKHR)))
    "pSwapchainImageCount" ::: Ptr Word32
pImageIndices <- Ptr ("pSwapchainImageCount" ::: Ptr Word32)
-> IO ("pSwapchainImageCount" ::: Ptr Word32)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr Word32) ((Ptr (PresentInfoKHR es)
p Ptr (PresentInfoKHR es)
-> Int -> Ptr ("pSwapchainImageCount" ::: Ptr Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr (Ptr Word32)))
    Vector Word32
pImageIndices' <- Int -> (Int -> IO Word32) -> IO (Vector Word32)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
swapchainCount) (\i :: Int
i -> ("pSwapchainImageCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pSwapchainImageCount" ::: Ptr Word32
pImageIndices ("pSwapchainImageCount" ::: Ptr Word32)
-> Int -> "pSwapchainImageCount" ::: Ptr Word32
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32)))
    Ptr Result
pResults <- Ptr (Ptr Result) -> IO (Ptr Result)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr Result) ((Ptr (PresentInfoKHR es)
p Ptr (PresentInfoKHR es) -> Int -> Ptr (Ptr Result)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr (Ptr Result)))
    PresentInfoKHR es -> IO (PresentInfoKHR es)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PresentInfoKHR es -> IO (PresentInfoKHR es))
-> PresentInfoKHR es -> IO (PresentInfoKHR es)
forall a b. (a -> b) -> a -> b
$ Chain es
-> Vector Semaphore
-> Vector SwapchainKHR
-> Vector Word32
-> Ptr Result
-> PresentInfoKHR es
forall (es :: [*]).
Chain es
-> Vector Semaphore
-> Vector SwapchainKHR
-> Vector Word32
-> Ptr Result
-> PresentInfoKHR es
PresentInfoKHR
             Chain es
next Vector Semaphore
pWaitSemaphores' Vector SwapchainKHR
pSwapchains' Vector Word32
pImageIndices' Ptr Result
pResults

instance es ~ '[] => Zero (PresentInfoKHR es) where
  zero :: PresentInfoKHR es
zero = Chain es
-> Vector Semaphore
-> Vector SwapchainKHR
-> Vector Word32
-> Ptr Result
-> PresentInfoKHR es
forall (es :: [*]).
Chain es
-> Vector Semaphore
-> Vector SwapchainKHR
-> Vector Word32
-> Ptr Result
-> PresentInfoKHR es
PresentInfoKHR
           ()
           Vector Semaphore
forall a. Monoid a => a
mempty
           Vector SwapchainKHR
forall a. Monoid a => a
mempty
           Vector Word32
forall a. Monoid a => a
mempty
           Ptr Result
forall a. Zero a => a
zero


-- | VkDeviceGroupPresentCapabilitiesKHR - Present capabilities from other
-- physical devices
--
-- = Description
--
-- @modes@ always has 'DEVICE_GROUP_PRESENT_MODE_LOCAL_BIT_KHR' set.
--
-- The present mode flags are also used when presenting an image, in
-- 'DeviceGroupPresentInfoKHR'::@mode@.
--
-- If a device group only includes a single physical device, then @modes@
-- /must/ equal 'DEVICE_GROUP_PRESENT_MODE_LOCAL_BIT_KHR'.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'DeviceGroupPresentModeFlagsKHR',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'getDeviceGroupPresentCapabilitiesKHR'
data DeviceGroupPresentCapabilitiesKHR = DeviceGroupPresentCapabilitiesKHR
  { -- | @presentMask@ is an array of
    -- 'Vulkan.Core10.APIConstants.MAX_DEVICE_GROUP_SIZE' @uint32_t@ masks,
    -- where the mask at element i is non-zero if physical device i has a
    -- presentation engine, and where bit j is set in element i if physical
    -- device i /can/ present swapchain images from physical device j. If
    -- element i is non-zero, then bit i /must/ be set.
    DeviceGroupPresentCapabilitiesKHR -> Vector Word32
presentMask :: Vector Word32
  , -- | @modes@ is a bitmask of 'DeviceGroupPresentModeFlagBitsKHR' indicating
    -- which device group presentation modes are supported.
    DeviceGroupPresentCapabilitiesKHR
-> "modes" ::: DeviceGroupPresentModeFlagsKHR
modes :: DeviceGroupPresentModeFlagsKHR
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DeviceGroupPresentCapabilitiesKHR)
#endif
deriving instance Show DeviceGroupPresentCapabilitiesKHR

instance ToCStruct DeviceGroupPresentCapabilitiesKHR where
  withCStruct :: DeviceGroupPresentCapabilitiesKHR
-> (("pDeviceGroupPresentCapabilities"
     ::: Ptr DeviceGroupPresentCapabilitiesKHR)
    -> IO b)
-> IO b
withCStruct x :: DeviceGroupPresentCapabilitiesKHR
x f :: ("pDeviceGroupPresentCapabilities"
 ::: Ptr DeviceGroupPresentCapabilitiesKHR)
-> IO b
f = Int
-> Int
-> (("pDeviceGroupPresentCapabilities"
     ::: Ptr DeviceGroupPresentCapabilitiesKHR)
    -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 152 8 ((("pDeviceGroupPresentCapabilities"
   ::: Ptr DeviceGroupPresentCapabilitiesKHR)
  -> IO b)
 -> IO b)
-> (("pDeviceGroupPresentCapabilities"
     ::: Ptr DeviceGroupPresentCapabilitiesKHR)
    -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pDeviceGroupPresentCapabilities"
::: Ptr DeviceGroupPresentCapabilitiesKHR
p -> ("pDeviceGroupPresentCapabilities"
 ::: Ptr DeviceGroupPresentCapabilitiesKHR)
-> DeviceGroupPresentCapabilitiesKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pDeviceGroupPresentCapabilities"
::: Ptr DeviceGroupPresentCapabilitiesKHR
p DeviceGroupPresentCapabilitiesKHR
x (("pDeviceGroupPresentCapabilities"
 ::: Ptr DeviceGroupPresentCapabilitiesKHR)
-> IO b
f "pDeviceGroupPresentCapabilities"
::: Ptr DeviceGroupPresentCapabilitiesKHR
p)
  pokeCStruct :: ("pDeviceGroupPresentCapabilities"
 ::: Ptr DeviceGroupPresentCapabilitiesKHR)
-> DeviceGroupPresentCapabilitiesKHR -> IO b -> IO b
pokeCStruct p :: "pDeviceGroupPresentCapabilities"
::: Ptr DeviceGroupPresentCapabilitiesKHR
p DeviceGroupPresentCapabilitiesKHR{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pDeviceGroupPresentCapabilities"
::: Ptr DeviceGroupPresentCapabilitiesKHR
p ("pDeviceGroupPresentCapabilities"
 ::: Ptr DeviceGroupPresentCapabilitiesKHR)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEVICE_GROUP_PRESENT_CAPABILITIES_KHR)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pDeviceGroupPresentCapabilities"
::: Ptr DeviceGroupPresentCapabilitiesKHR
p ("pDeviceGroupPresentCapabilities"
 ::: Ptr DeviceGroupPresentCapabilitiesKHR)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ((Vector Word32 -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Word32 -> Int) -> Vector Word32 -> Int
forall a b. (a -> b) -> a -> b
$ (Vector Word32
presentMask)) Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
forall a. Integral a => a
MAX_DEVICE_GROUP_SIZE) (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 "" "presentMask is too long, a maximum of MAX_DEVICE_GROUP_SIZE elements are allowed" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
    (Int -> Word32 -> IO ()) -> Vector Word32 -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Word32
e -> ("pSwapchainImageCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (FixedArray MAX_DEVICE_GROUP_SIZE Word32)
-> "pSwapchainImageCount" ::: Ptr Word32
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr (("pDeviceGroupPresentCapabilities"
::: Ptr DeviceGroupPresentCapabilitiesKHR
p ("pDeviceGroupPresentCapabilities"
 ::: Ptr DeviceGroupPresentCapabilitiesKHR)
-> Int -> Ptr (FixedArray MAX_DEVICE_GROUP_SIZE Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (FixedArray MAX_DEVICE_GROUP_SIZE Word32)))) ("pSwapchainImageCount" ::: Ptr Word32)
-> Int -> "pSwapchainImageCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32) (Word32
e)) (Vector Word32
presentMask)
    ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pDeviceGroupPresentCapabilities"
::: Ptr DeviceGroupPresentCapabilitiesKHR
p ("pDeviceGroupPresentCapabilities"
 ::: Ptr DeviceGroupPresentCapabilitiesKHR)
-> Int
-> "pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 144 :: Ptr DeviceGroupPresentModeFlagsKHR)) ("modes" ::: DeviceGroupPresentModeFlagsKHR
modes)
    IO b
f
  cStructSize :: Int
cStructSize = 152
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: ("pDeviceGroupPresentCapabilities"
 ::: Ptr DeviceGroupPresentCapabilitiesKHR)
-> IO b -> IO b
pokeZeroCStruct p :: "pDeviceGroupPresentCapabilities"
::: Ptr DeviceGroupPresentCapabilitiesKHR
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pDeviceGroupPresentCapabilities"
::: Ptr DeviceGroupPresentCapabilitiesKHR
p ("pDeviceGroupPresentCapabilities"
 ::: Ptr DeviceGroupPresentCapabilitiesKHR)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEVICE_GROUP_PRESENT_CAPABILITIES_KHR)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pDeviceGroupPresentCapabilities"
::: Ptr DeviceGroupPresentCapabilitiesKHR
p ("pDeviceGroupPresentCapabilities"
 ::: Ptr DeviceGroupPresentCapabilitiesKHR)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any -> Int) -> Vector Any -> Int
forall a b. (a -> b) -> a -> b
$ (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
forall a. Integral a => a
MAX_DEVICE_GROUP_SIZE) (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 "" "presentMask is too long, a maximum of MAX_DEVICE_GROUP_SIZE elements are allowed" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
    (Int -> Word32 -> IO ()) -> Vector Word32 -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Word32
e -> ("pSwapchainImageCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (FixedArray MAX_DEVICE_GROUP_SIZE Word32)
-> "pSwapchainImageCount" ::: Ptr Word32
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr (("pDeviceGroupPresentCapabilities"
::: Ptr DeviceGroupPresentCapabilitiesKHR
p ("pDeviceGroupPresentCapabilities"
 ::: Ptr DeviceGroupPresentCapabilitiesKHR)
-> Int -> Ptr (FixedArray MAX_DEVICE_GROUP_SIZE Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (FixedArray MAX_DEVICE_GROUP_SIZE Word32)))) ("pSwapchainImageCount" ::: Ptr Word32)
-> Int -> "pSwapchainImageCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32) (Word32
e)) (Vector Word32
forall a. Monoid a => a
mempty)
    ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pDeviceGroupPresentCapabilities"
::: Ptr DeviceGroupPresentCapabilitiesKHR
p ("pDeviceGroupPresentCapabilities"
 ::: Ptr DeviceGroupPresentCapabilitiesKHR)
-> Int
-> "pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 144 :: Ptr DeviceGroupPresentModeFlagsKHR)) ("modes" ::: DeviceGroupPresentModeFlagsKHR
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct DeviceGroupPresentCapabilitiesKHR where
  peekCStruct :: ("pDeviceGroupPresentCapabilities"
 ::: Ptr DeviceGroupPresentCapabilitiesKHR)
-> IO DeviceGroupPresentCapabilitiesKHR
peekCStruct p :: "pDeviceGroupPresentCapabilities"
::: Ptr DeviceGroupPresentCapabilitiesKHR
p = do
    Vector Word32
presentMask <- Int -> (Int -> IO Word32) -> IO (Vector Word32)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Int
forall a. Integral a => a
MAX_DEVICE_GROUP_SIZE) (\i :: Int
i -> ("pSwapchainImageCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 (((Ptr (FixedArray MAX_DEVICE_GROUP_SIZE Word32)
-> "pSwapchainImageCount" ::: Ptr Word32
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr @Word32 (("pDeviceGroupPresentCapabilities"
::: Ptr DeviceGroupPresentCapabilitiesKHR
p ("pDeviceGroupPresentCapabilities"
 ::: Ptr DeviceGroupPresentCapabilitiesKHR)
-> Int -> Ptr (FixedArray MAX_DEVICE_GROUP_SIZE Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (FixedArray MAX_DEVICE_GROUP_SIZE Word32)))) ("pSwapchainImageCount" ::: Ptr Word32)
-> Int -> "pSwapchainImageCount" ::: Ptr Word32
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32)))
    "modes" ::: DeviceGroupPresentModeFlagsKHR
modes <- ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall a. Storable a => Ptr a -> IO a
peek @DeviceGroupPresentModeFlagsKHR (("pDeviceGroupPresentCapabilities"
::: Ptr DeviceGroupPresentCapabilitiesKHR
p ("pDeviceGroupPresentCapabilities"
 ::: Ptr DeviceGroupPresentCapabilitiesKHR)
-> Int
-> "pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 144 :: Ptr DeviceGroupPresentModeFlagsKHR))
    DeviceGroupPresentCapabilitiesKHR
-> IO DeviceGroupPresentCapabilitiesKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DeviceGroupPresentCapabilitiesKHR
 -> IO DeviceGroupPresentCapabilitiesKHR)
-> DeviceGroupPresentCapabilitiesKHR
-> IO DeviceGroupPresentCapabilitiesKHR
forall a b. (a -> b) -> a -> b
$ Vector Word32
-> ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> DeviceGroupPresentCapabilitiesKHR
DeviceGroupPresentCapabilitiesKHR
             Vector Word32
presentMask "modes" ::: DeviceGroupPresentModeFlagsKHR
modes

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

instance Zero DeviceGroupPresentCapabilitiesKHR where
  zero :: DeviceGroupPresentCapabilitiesKHR
zero = Vector Word32
-> ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> DeviceGroupPresentCapabilitiesKHR
DeviceGroupPresentCapabilitiesKHR
           Vector Word32
forall a. Monoid a => a
mempty
           "modes" ::: DeviceGroupPresentModeFlagsKHR
forall a. Zero a => a
zero


-- | VkImageSwapchainCreateInfoKHR - Specify that an image will be bound to
-- swapchain memory
--
-- == Valid Usage
--
-- -   If @swapchain@ is not 'Vulkan.Core10.APIConstants.NULL_HANDLE', the
--     fields of 'Vulkan.Core10.Image.ImageCreateInfo' /must/ match the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#swapchain-wsi-image-create-info implied image creation parameters>
--     of the swapchain
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_IMAGE_SWAPCHAIN_CREATE_INFO_KHR'
--
-- -   If @swapchain@ is not 'Vulkan.Core10.APIConstants.NULL_HANDLE',
--     @swapchain@ /must/ be a valid
--     'Vulkan.Extensions.Handles.SwapchainKHR' handle
--
-- = See Also
--
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'Vulkan.Extensions.Handles.SwapchainKHR'
data ImageSwapchainCreateInfoKHR = ImageSwapchainCreateInfoKHR
  { -- | @swapchain@ is 'Vulkan.Core10.APIConstants.NULL_HANDLE' or a handle of a
    -- swapchain that the image will be bound to.
    ImageSwapchainCreateInfoKHR -> SwapchainKHR
swapchain :: SwapchainKHR }
  deriving (Typeable, ImageSwapchainCreateInfoKHR -> ImageSwapchainCreateInfoKHR -> Bool
(ImageSwapchainCreateInfoKHR
 -> ImageSwapchainCreateInfoKHR -> Bool)
-> (ImageSwapchainCreateInfoKHR
    -> ImageSwapchainCreateInfoKHR -> Bool)
-> Eq ImageSwapchainCreateInfoKHR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImageSwapchainCreateInfoKHR -> ImageSwapchainCreateInfoKHR -> Bool
$c/= :: ImageSwapchainCreateInfoKHR -> ImageSwapchainCreateInfoKHR -> Bool
== :: ImageSwapchainCreateInfoKHR -> ImageSwapchainCreateInfoKHR -> Bool
$c== :: ImageSwapchainCreateInfoKHR -> ImageSwapchainCreateInfoKHR -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ImageSwapchainCreateInfoKHR)
#endif
deriving instance Show ImageSwapchainCreateInfoKHR

instance ToCStruct ImageSwapchainCreateInfoKHR where
  withCStruct :: ImageSwapchainCreateInfoKHR
-> (Ptr ImageSwapchainCreateInfoKHR -> IO b) -> IO b
withCStruct x :: ImageSwapchainCreateInfoKHR
x f :: Ptr ImageSwapchainCreateInfoKHR -> IO b
f = Int -> Int -> (Ptr ImageSwapchainCreateInfoKHR -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr ImageSwapchainCreateInfoKHR -> IO b) -> IO b)
-> (Ptr ImageSwapchainCreateInfoKHR -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr ImageSwapchainCreateInfoKHR
p -> Ptr ImageSwapchainCreateInfoKHR
-> ImageSwapchainCreateInfoKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ImageSwapchainCreateInfoKHR
p ImageSwapchainCreateInfoKHR
x (Ptr ImageSwapchainCreateInfoKHR -> IO b
f Ptr ImageSwapchainCreateInfoKHR
p)
  pokeCStruct :: Ptr ImageSwapchainCreateInfoKHR
-> ImageSwapchainCreateInfoKHR -> IO b -> IO b
pokeCStruct p :: Ptr ImageSwapchainCreateInfoKHR
p ImageSwapchainCreateInfoKHR{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageSwapchainCreateInfoKHR
p Ptr ImageSwapchainCreateInfoKHR -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMAGE_SWAPCHAIN_CREATE_INFO_KHR)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageSwapchainCreateInfoKHR
p Ptr ImageSwapchainCreateInfoKHR -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    ("pSwapchain" ::: Ptr SwapchainKHR) -> SwapchainKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageSwapchainCreateInfoKHR
p Ptr ImageSwapchainCreateInfoKHR
-> Int -> "pSwapchain" ::: Ptr SwapchainKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr SwapchainKHR)) (SwapchainKHR
swapchain)
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr ImageSwapchainCreateInfoKHR -> IO b -> IO b
pokeZeroCStruct p :: Ptr ImageSwapchainCreateInfoKHR
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageSwapchainCreateInfoKHR
p Ptr ImageSwapchainCreateInfoKHR -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMAGE_SWAPCHAIN_CREATE_INFO_KHR)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImageSwapchainCreateInfoKHR
p Ptr ImageSwapchainCreateInfoKHR -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    IO b
f

instance FromCStruct ImageSwapchainCreateInfoKHR where
  peekCStruct :: Ptr ImageSwapchainCreateInfoKHR -> IO ImageSwapchainCreateInfoKHR
peekCStruct p :: Ptr ImageSwapchainCreateInfoKHR
p = do
    SwapchainKHR
swapchain <- ("pSwapchain" ::: Ptr SwapchainKHR) -> IO SwapchainKHR
forall a. Storable a => Ptr a -> IO a
peek @SwapchainKHR ((Ptr ImageSwapchainCreateInfoKHR
p Ptr ImageSwapchainCreateInfoKHR
-> Int -> "pSwapchain" ::: Ptr SwapchainKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr SwapchainKHR))
    ImageSwapchainCreateInfoKHR -> IO ImageSwapchainCreateInfoKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ImageSwapchainCreateInfoKHR -> IO ImageSwapchainCreateInfoKHR)
-> ImageSwapchainCreateInfoKHR -> IO ImageSwapchainCreateInfoKHR
forall a b. (a -> b) -> a -> b
$ SwapchainKHR -> ImageSwapchainCreateInfoKHR
ImageSwapchainCreateInfoKHR
             SwapchainKHR
swapchain

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

instance Zero ImageSwapchainCreateInfoKHR where
  zero :: ImageSwapchainCreateInfoKHR
zero = SwapchainKHR -> ImageSwapchainCreateInfoKHR
ImageSwapchainCreateInfoKHR
           SwapchainKHR
forall a. Zero a => a
zero


-- | VkBindImageMemorySwapchainInfoKHR - Structure specifying swapchain image
-- memory to bind to
--
-- = Description
--
-- If @swapchain@ is not @NULL@, the @swapchain@ and @imageIndex@ are used
-- to determine the memory that the image is bound to, instead of @memory@
-- and @memoryOffset@.
--
-- Memory /can/ be bound to a swapchain and use the @pDeviceIndices@ or
-- @pSplitInstanceBindRegions@ members of
-- 'Vulkan.Core11.Promoted_From_VK_KHR_device_groupAndVK_KHR_bind_memory2.BindImageMemoryDeviceGroupInfo'.
--
-- == Valid Usage
--
-- -   @imageIndex@ /must/ be less than the number of images in @swapchain@
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_BIND_IMAGE_MEMORY_SWAPCHAIN_INFO_KHR'
--
-- -   @swapchain@ /must/ be a valid
--     'Vulkan.Extensions.Handles.SwapchainKHR' handle
--
-- == Host Synchronization
--
-- -   Host access to @swapchain@ /must/ be externally synchronized
--
-- = See Also
--
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'Vulkan.Extensions.Handles.SwapchainKHR'
data BindImageMemorySwapchainInfoKHR = BindImageMemorySwapchainInfoKHR
  { -- | @swapchain@ is 'Vulkan.Core10.APIConstants.NULL_HANDLE' or a swapchain
    -- handle.
    BindImageMemorySwapchainInfoKHR -> SwapchainKHR
swapchain :: SwapchainKHR
  , -- | @imageIndex@ is an image index within @swapchain@.
    BindImageMemorySwapchainInfoKHR -> Word32
imageIndex :: Word32
  }
  deriving (Typeable, BindImageMemorySwapchainInfoKHR
-> BindImageMemorySwapchainInfoKHR -> Bool
(BindImageMemorySwapchainInfoKHR
 -> BindImageMemorySwapchainInfoKHR -> Bool)
-> (BindImageMemorySwapchainInfoKHR
    -> BindImageMemorySwapchainInfoKHR -> Bool)
-> Eq BindImageMemorySwapchainInfoKHR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BindImageMemorySwapchainInfoKHR
-> BindImageMemorySwapchainInfoKHR -> Bool
$c/= :: BindImageMemorySwapchainInfoKHR
-> BindImageMemorySwapchainInfoKHR -> Bool
== :: BindImageMemorySwapchainInfoKHR
-> BindImageMemorySwapchainInfoKHR -> Bool
$c== :: BindImageMemorySwapchainInfoKHR
-> BindImageMemorySwapchainInfoKHR -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (BindImageMemorySwapchainInfoKHR)
#endif
deriving instance Show BindImageMemorySwapchainInfoKHR

instance ToCStruct BindImageMemorySwapchainInfoKHR where
  withCStruct :: BindImageMemorySwapchainInfoKHR
-> (Ptr BindImageMemorySwapchainInfoKHR -> IO b) -> IO b
withCStruct x :: BindImageMemorySwapchainInfoKHR
x f :: Ptr BindImageMemorySwapchainInfoKHR -> IO b
f = Int -> Int -> (Ptr BindImageMemorySwapchainInfoKHR -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 32 8 ((Ptr BindImageMemorySwapchainInfoKHR -> IO b) -> IO b)
-> (Ptr BindImageMemorySwapchainInfoKHR -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr BindImageMemorySwapchainInfoKHR
p -> Ptr BindImageMemorySwapchainInfoKHR
-> BindImageMemorySwapchainInfoKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr BindImageMemorySwapchainInfoKHR
p BindImageMemorySwapchainInfoKHR
x (Ptr BindImageMemorySwapchainInfoKHR -> IO b
f Ptr BindImageMemorySwapchainInfoKHR
p)
  pokeCStruct :: Ptr BindImageMemorySwapchainInfoKHR
-> BindImageMemorySwapchainInfoKHR -> IO b -> IO b
pokeCStruct p :: Ptr BindImageMemorySwapchainInfoKHR
p BindImageMemorySwapchainInfoKHR{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BindImageMemorySwapchainInfoKHR
p Ptr BindImageMemorySwapchainInfoKHR -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_BIND_IMAGE_MEMORY_SWAPCHAIN_INFO_KHR)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BindImageMemorySwapchainInfoKHR
p Ptr BindImageMemorySwapchainInfoKHR -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    ("pSwapchain" ::: Ptr SwapchainKHR) -> SwapchainKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BindImageMemorySwapchainInfoKHR
p Ptr BindImageMemorySwapchainInfoKHR
-> Int -> "pSwapchain" ::: Ptr SwapchainKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr SwapchainKHR)) (SwapchainKHR
swapchain)
    ("pSwapchainImageCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BindImageMemorySwapchainInfoKHR
p Ptr BindImageMemorySwapchainInfoKHR
-> Int -> "pSwapchainImageCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32)) (Word32
imageIndex)
    IO b
f
  cStructSize :: Int
cStructSize = 32
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr BindImageMemorySwapchainInfoKHR -> IO b -> IO b
pokeZeroCStruct p :: Ptr BindImageMemorySwapchainInfoKHR
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BindImageMemorySwapchainInfoKHR
p Ptr BindImageMemorySwapchainInfoKHR -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_BIND_IMAGE_MEMORY_SWAPCHAIN_INFO_KHR)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BindImageMemorySwapchainInfoKHR
p Ptr BindImageMemorySwapchainInfoKHR -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    ("pSwapchain" ::: Ptr SwapchainKHR) -> SwapchainKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BindImageMemorySwapchainInfoKHR
p Ptr BindImageMemorySwapchainInfoKHR
-> Int -> "pSwapchain" ::: Ptr SwapchainKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr SwapchainKHR)) (SwapchainKHR
forall a. Zero a => a
zero)
    ("pSwapchainImageCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr BindImageMemorySwapchainInfoKHR
p Ptr BindImageMemorySwapchainInfoKHR
-> Int -> "pSwapchainImageCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct BindImageMemorySwapchainInfoKHR where
  peekCStruct :: Ptr BindImageMemorySwapchainInfoKHR
-> IO BindImageMemorySwapchainInfoKHR
peekCStruct p :: Ptr BindImageMemorySwapchainInfoKHR
p = do
    SwapchainKHR
swapchain <- ("pSwapchain" ::: Ptr SwapchainKHR) -> IO SwapchainKHR
forall a. Storable a => Ptr a -> IO a
peek @SwapchainKHR ((Ptr BindImageMemorySwapchainInfoKHR
p Ptr BindImageMemorySwapchainInfoKHR
-> Int -> "pSwapchain" ::: Ptr SwapchainKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr SwapchainKHR))
    Word32
imageIndex <- ("pSwapchainImageCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr BindImageMemorySwapchainInfoKHR
p Ptr BindImageMemorySwapchainInfoKHR
-> Int -> "pSwapchainImageCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32))
    BindImageMemorySwapchainInfoKHR
-> IO BindImageMemorySwapchainInfoKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (BindImageMemorySwapchainInfoKHR
 -> IO BindImageMemorySwapchainInfoKHR)
-> BindImageMemorySwapchainInfoKHR
-> IO BindImageMemorySwapchainInfoKHR
forall a b. (a -> b) -> a -> b
$ SwapchainKHR -> Word32 -> BindImageMemorySwapchainInfoKHR
BindImageMemorySwapchainInfoKHR
             SwapchainKHR
swapchain Word32
imageIndex

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

instance Zero BindImageMemorySwapchainInfoKHR where
  zero :: BindImageMemorySwapchainInfoKHR
zero = SwapchainKHR -> Word32 -> BindImageMemorySwapchainInfoKHR
BindImageMemorySwapchainInfoKHR
           SwapchainKHR
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero


-- | VkAcquireNextImageInfoKHR - Structure specifying parameters of the
-- acquire
--
-- = Description
--
-- If 'acquireNextImageKHR' is used, the device mask is considered to
-- include all physical devices in the logical device.
--
-- Note
--
-- 'acquireNextImage2KHR' signals at most one semaphore, even if the
-- application requests waiting for multiple physical devices to be ready
-- via the @deviceMask@. However, only a single physical device /can/ wait
-- on that semaphore, since the semaphore becomes unsignaled when the wait
-- succeeds. For other physical devices to wait for the image to be ready,
-- it is necessary for the application to submit semaphore signal
-- operation(s) to that first physical device to signal additional
-- semaphore(s) after the wait succeeds, which the other physical device(s)
-- /can/ wait upon.
--
-- == Valid Usage
--
-- -   @swapchain@ /must/ not be in the retired state
--
-- -   If @semaphore@ is not 'Vulkan.Core10.APIConstants.NULL_HANDLE' it
--     /must/ be unsignaled
--
-- -   If @semaphore@ is not 'Vulkan.Core10.APIConstants.NULL_HANDLE' it
--     /must/ not have any uncompleted signal or wait operations pending
--
-- -   If @fence@ is not 'Vulkan.Core10.APIConstants.NULL_HANDLE' it /must/
--     be unsignaled and /must/ not be associated with any other queue
--     command that has not yet completed execution on that queue
--
-- -   @semaphore@ and @fence@ /must/ not both be equal to
--     'Vulkan.Core10.APIConstants.NULL_HANDLE'
--
-- -   @deviceMask@ /must/ be a valid device mask
--
-- -   @deviceMask@ /must/ not be zero
--
-- -   @semaphore@ /must/ have a
--     'Vulkan.Core12.Enums.SemaphoreType.SemaphoreType' of
--     'Vulkan.Core12.Enums.SemaphoreType.SEMAPHORE_TYPE_BINARY'
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_ACQUIRE_NEXT_IMAGE_INFO_KHR'
--
-- -   @pNext@ /must/ be @NULL@
--
-- -   @swapchain@ /must/ be a valid
--     'Vulkan.Extensions.Handles.SwapchainKHR' handle
--
-- -   If @semaphore@ is not 'Vulkan.Core10.APIConstants.NULL_HANDLE',
--     @semaphore@ /must/ be a valid 'Vulkan.Core10.Handles.Semaphore'
--     handle
--
-- -   If @fence@ is not 'Vulkan.Core10.APIConstants.NULL_HANDLE', @fence@
--     /must/ be a valid 'Vulkan.Core10.Handles.Fence' handle
--
-- -   Each of @fence@, @semaphore@, and @swapchain@ that are valid handles
--     of non-ignored parameters /must/ have been created, allocated, or
--     retrieved from the same 'Vulkan.Core10.Handles.Instance'
--
-- == Host Synchronization
--
-- -   Host access to @swapchain@ /must/ be externally synchronized
--
-- -   Host access to @semaphore@ /must/ be externally synchronized
--
-- -   Host access to @fence@ /must/ be externally synchronized
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.Fence', 'Vulkan.Core10.Handles.Semaphore',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'Vulkan.Extensions.Handles.SwapchainKHR', 'acquireNextImage2KHR'
data AcquireNextImageInfoKHR = AcquireNextImageInfoKHR
  { -- | @swapchain@ is a non-retired swapchain from which an image is acquired.
    AcquireNextImageInfoKHR -> SwapchainKHR
swapchain :: SwapchainKHR
  , -- | @timeout@ specifies how long the function waits, in nanoseconds, if no
    -- image is available.
    AcquireNextImageInfoKHR -> Word64
timeout :: Word64
  , -- | @semaphore@ is 'Vulkan.Core10.APIConstants.NULL_HANDLE' or a semaphore
    -- to signal.
    AcquireNextImageInfoKHR -> Semaphore
semaphore :: Semaphore
  , -- | @fence@ is 'Vulkan.Core10.APIConstants.NULL_HANDLE' or a fence to
    -- signal.
    AcquireNextImageInfoKHR -> Fence
fence :: Fence
  , -- | @deviceMask@ is a mask of physical devices for which the swapchain image
    -- will be ready to use when the semaphore or fence is signaled.
    AcquireNextImageInfoKHR -> Word32
deviceMask :: Word32
  }
  deriving (Typeable, AcquireNextImageInfoKHR -> AcquireNextImageInfoKHR -> Bool
(AcquireNextImageInfoKHR -> AcquireNextImageInfoKHR -> Bool)
-> (AcquireNextImageInfoKHR -> AcquireNextImageInfoKHR -> Bool)
-> Eq AcquireNextImageInfoKHR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AcquireNextImageInfoKHR -> AcquireNextImageInfoKHR -> Bool
$c/= :: AcquireNextImageInfoKHR -> AcquireNextImageInfoKHR -> Bool
== :: AcquireNextImageInfoKHR -> AcquireNextImageInfoKHR -> Bool
$c== :: AcquireNextImageInfoKHR -> AcquireNextImageInfoKHR -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (AcquireNextImageInfoKHR)
#endif
deriving instance Show AcquireNextImageInfoKHR

instance ToCStruct AcquireNextImageInfoKHR where
  withCStruct :: AcquireNextImageInfoKHR
-> (Ptr AcquireNextImageInfoKHR -> IO b) -> IO b
withCStruct x :: AcquireNextImageInfoKHR
x f :: Ptr AcquireNextImageInfoKHR -> IO b
f = Int -> Int -> (Ptr AcquireNextImageInfoKHR -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 56 8 ((Ptr AcquireNextImageInfoKHR -> IO b) -> IO b)
-> (Ptr AcquireNextImageInfoKHR -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr AcquireNextImageInfoKHR
p -> Ptr AcquireNextImageInfoKHR
-> AcquireNextImageInfoKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr AcquireNextImageInfoKHR
p AcquireNextImageInfoKHR
x (Ptr AcquireNextImageInfoKHR -> IO b
f Ptr AcquireNextImageInfoKHR
p)
  pokeCStruct :: Ptr AcquireNextImageInfoKHR
-> AcquireNextImageInfoKHR -> IO b -> IO b
pokeCStruct p :: Ptr AcquireNextImageInfoKHR
p AcquireNextImageInfoKHR{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AcquireNextImageInfoKHR
p Ptr AcquireNextImageInfoKHR -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ACQUIRE_NEXT_IMAGE_INFO_KHR)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AcquireNextImageInfoKHR
p Ptr AcquireNextImageInfoKHR -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    ("pSwapchain" ::: Ptr SwapchainKHR) -> SwapchainKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AcquireNextImageInfoKHR
p Ptr AcquireNextImageInfoKHR
-> Int -> "pSwapchain" ::: Ptr SwapchainKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr SwapchainKHR)) (SwapchainKHR
swapchain)
    Ptr Word64 -> Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AcquireNextImageInfoKHR
p Ptr AcquireNextImageInfoKHR -> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word64)) (Word64
timeout)
    Ptr Semaphore -> Semaphore -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AcquireNextImageInfoKHR
p Ptr AcquireNextImageInfoKHR -> Int -> Ptr Semaphore
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Semaphore)) (Semaphore
semaphore)
    Ptr Fence -> Fence -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AcquireNextImageInfoKHR
p Ptr AcquireNextImageInfoKHR -> Int -> Ptr Fence
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Fence)) (Fence
fence)
    ("pSwapchainImageCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AcquireNextImageInfoKHR
p Ptr AcquireNextImageInfoKHR
-> Int -> "pSwapchainImageCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Word32)) (Word32
deviceMask)
    IO b
f
  cStructSize :: Int
cStructSize = 56
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr AcquireNextImageInfoKHR -> IO b -> IO b
pokeZeroCStruct p :: Ptr AcquireNextImageInfoKHR
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AcquireNextImageInfoKHR
p Ptr AcquireNextImageInfoKHR -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ACQUIRE_NEXT_IMAGE_INFO_KHR)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AcquireNextImageInfoKHR
p Ptr AcquireNextImageInfoKHR -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    ("pSwapchain" ::: Ptr SwapchainKHR) -> SwapchainKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AcquireNextImageInfoKHR
p Ptr AcquireNextImageInfoKHR
-> Int -> "pSwapchain" ::: Ptr SwapchainKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr SwapchainKHR)) (SwapchainKHR
forall a. Zero a => a
zero)
    Ptr Word64 -> Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AcquireNextImageInfoKHR
p Ptr AcquireNextImageInfoKHR -> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word64)) (Word64
forall a. Zero a => a
zero)
    ("pSwapchainImageCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AcquireNextImageInfoKHR
p Ptr AcquireNextImageInfoKHR
-> Int -> "pSwapchainImageCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct AcquireNextImageInfoKHR where
  peekCStruct :: Ptr AcquireNextImageInfoKHR -> IO AcquireNextImageInfoKHR
peekCStruct p :: Ptr AcquireNextImageInfoKHR
p = do
    SwapchainKHR
swapchain <- ("pSwapchain" ::: Ptr SwapchainKHR) -> IO SwapchainKHR
forall a. Storable a => Ptr a -> IO a
peek @SwapchainKHR ((Ptr AcquireNextImageInfoKHR
p Ptr AcquireNextImageInfoKHR
-> Int -> "pSwapchain" ::: Ptr SwapchainKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr SwapchainKHR))
    Word64
timeout <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek @Word64 ((Ptr AcquireNextImageInfoKHR
p Ptr AcquireNextImageInfoKHR -> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word64))
    Semaphore
semaphore <- Ptr Semaphore -> IO Semaphore
forall a. Storable a => Ptr a -> IO a
peek @Semaphore ((Ptr AcquireNextImageInfoKHR
p Ptr AcquireNextImageInfoKHR -> Int -> Ptr Semaphore
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Semaphore))
    Fence
fence <- Ptr Fence -> IO Fence
forall a. Storable a => Ptr a -> IO a
peek @Fence ((Ptr AcquireNextImageInfoKHR
p Ptr AcquireNextImageInfoKHR -> Int -> Ptr Fence
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Fence))
    Word32
deviceMask <- ("pSwapchainImageCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr AcquireNextImageInfoKHR
p Ptr AcquireNextImageInfoKHR
-> Int -> "pSwapchainImageCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Word32))
    AcquireNextImageInfoKHR -> IO AcquireNextImageInfoKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AcquireNextImageInfoKHR -> IO AcquireNextImageInfoKHR)
-> AcquireNextImageInfoKHR -> IO AcquireNextImageInfoKHR
forall a b. (a -> b) -> a -> b
$ SwapchainKHR
-> Word64
-> Semaphore
-> Fence
-> Word32
-> AcquireNextImageInfoKHR
AcquireNextImageInfoKHR
             SwapchainKHR
swapchain Word64
timeout Semaphore
semaphore Fence
fence Word32
deviceMask

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

instance Zero AcquireNextImageInfoKHR where
  zero :: AcquireNextImageInfoKHR
zero = SwapchainKHR
-> Word64
-> Semaphore
-> Fence
-> Word32
-> AcquireNextImageInfoKHR
AcquireNextImageInfoKHR
           SwapchainKHR
forall a. Zero a => a
zero
           Word64
forall a. Zero a => a
zero
           Semaphore
forall a. Zero a => a
zero
           Fence
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero


-- | VkDeviceGroupPresentInfoKHR - Mode and mask controlling which physical
-- devices\' images are presented
--
-- = Description
--
-- If @mode@ is 'DEVICE_GROUP_PRESENT_MODE_LOCAL_BIT_KHR', then each
-- element of @pDeviceMasks@ selects which instance of the swapchain image
-- is presented. Each element of @pDeviceMasks@ /must/ have exactly one bit
-- set, and the corresponding physical device /must/ have a presentation
-- engine as reported by 'DeviceGroupPresentCapabilitiesKHR'.
--
-- If @mode@ is 'DEVICE_GROUP_PRESENT_MODE_REMOTE_BIT_KHR', then each
-- element of @pDeviceMasks@ selects which instance of the swapchain image
-- is presented. Each element of @pDeviceMasks@ /must/ have exactly one bit
-- set, and some physical device in the logical device /must/ include that
-- bit in its 'DeviceGroupPresentCapabilitiesKHR'::@presentMask@.
--
-- If @mode@ is 'DEVICE_GROUP_PRESENT_MODE_SUM_BIT_KHR', then each element
-- of @pDeviceMasks@ selects which instances of the swapchain image are
-- component-wise summed and the sum of those images is presented. If the
-- sum in any component is outside the representable range, the value of
-- that component is undefined. Each element of @pDeviceMasks@ /must/ have
-- a value for which all set bits are set in one of the elements of
-- 'DeviceGroupPresentCapabilitiesKHR'::@presentMask@.
--
-- If @mode@ is 'DEVICE_GROUP_PRESENT_MODE_LOCAL_MULTI_DEVICE_BIT_KHR',
-- then each element of @pDeviceMasks@ selects which instance(s) of the
-- swapchain images are presented. For each bit set in each element of
-- @pDeviceMasks@, the corresponding physical device /must/ have a
-- presentation engine as reported by 'DeviceGroupPresentCapabilitiesKHR'.
--
-- If 'DeviceGroupPresentInfoKHR' is not provided or @swapchainCount@ is
-- zero then the masks are considered to be @1@. If
-- 'DeviceGroupPresentInfoKHR' is not provided, @mode@ is considered to be
-- 'DEVICE_GROUP_PRESENT_MODE_LOCAL_BIT_KHR'.
--
-- == Valid Usage
--
-- -   @swapchainCount@ /must/ equal @0@ or
--     'PresentInfoKHR'::@swapchainCount@
--
-- -   If @mode@ is 'DEVICE_GROUP_PRESENT_MODE_LOCAL_BIT_KHR', then each
--     element of @pDeviceMasks@ /must/ have exactly one bit set, and the
--     corresponding element of
--     'DeviceGroupPresentCapabilitiesKHR'::@presentMask@ /must/ be
--     non-zero
--
-- -   If @mode@ is 'DEVICE_GROUP_PRESENT_MODE_REMOTE_BIT_KHR', then each
--     element of @pDeviceMasks@ /must/ have exactly one bit set, and some
--     physical device in the logical device /must/ include that bit in its
--     'DeviceGroupPresentCapabilitiesKHR'::@presentMask@
--
-- -   If @mode@ is 'DEVICE_GROUP_PRESENT_MODE_SUM_BIT_KHR', then each
--     element of @pDeviceMasks@ /must/ have a value for which all set bits
--     are set in one of the elements of
--     'DeviceGroupPresentCapabilitiesKHR'::@presentMask@
--
-- -   If @mode@ is 'DEVICE_GROUP_PRESENT_MODE_LOCAL_MULTI_DEVICE_BIT_KHR',
--     then for each bit set in each element of @pDeviceMasks@, the
--     corresponding element of
--     'DeviceGroupPresentCapabilitiesKHR'::@presentMask@ /must/ be
--     non-zero
--
-- -   The value of each element of @pDeviceMasks@ /must/ be equal to the
--     device mask passed in 'AcquireNextImageInfoKHR'::@deviceMask@ when
--     the image index was last acquired
--
-- -   @mode@ /must/ have exactly one bit set, and that bit /must/ have
--     been included in 'DeviceGroupSwapchainCreateInfoKHR'::@modes@
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_DEVICE_GROUP_PRESENT_INFO_KHR'
--
-- -   If @swapchainCount@ is not @0@, @pDeviceMasks@ /must/ be a valid
--     pointer to an array of @swapchainCount@ @uint32_t@ values
--
-- -   @mode@ /must/ be a valid 'DeviceGroupPresentModeFlagBitsKHR' value
--
-- = See Also
--
-- 'DeviceGroupPresentModeFlagBitsKHR',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data DeviceGroupPresentInfoKHR = DeviceGroupPresentInfoKHR
  { -- | @pDeviceMasks@ is a pointer to an array of device masks, one for each
    -- element of 'PresentInfoKHR'::pSwapchains.
    DeviceGroupPresentInfoKHR -> Vector Word32
deviceMasks :: Vector Word32
  , -- | @mode@ is the device group present mode that will be used for this
    -- present.
    DeviceGroupPresentInfoKHR
-> "modes" ::: DeviceGroupPresentModeFlagsKHR
mode :: DeviceGroupPresentModeFlagBitsKHR
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DeviceGroupPresentInfoKHR)
#endif
deriving instance Show DeviceGroupPresentInfoKHR

instance ToCStruct DeviceGroupPresentInfoKHR where
  withCStruct :: DeviceGroupPresentInfoKHR
-> (Ptr DeviceGroupPresentInfoKHR -> IO b) -> IO b
withCStruct x :: DeviceGroupPresentInfoKHR
x f :: Ptr DeviceGroupPresentInfoKHR -> IO b
f = Int -> Int -> (Ptr DeviceGroupPresentInfoKHR -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 40 8 ((Ptr DeviceGroupPresentInfoKHR -> IO b) -> IO b)
-> (Ptr DeviceGroupPresentInfoKHR -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr DeviceGroupPresentInfoKHR
p -> Ptr DeviceGroupPresentInfoKHR
-> DeviceGroupPresentInfoKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DeviceGroupPresentInfoKHR
p DeviceGroupPresentInfoKHR
x (Ptr DeviceGroupPresentInfoKHR -> IO b
f Ptr DeviceGroupPresentInfoKHR
p)
  pokeCStruct :: Ptr DeviceGroupPresentInfoKHR
-> DeviceGroupPresentInfoKHR -> IO b -> IO b
pokeCStruct p :: Ptr DeviceGroupPresentInfoKHR
p DeviceGroupPresentInfoKHR{..} f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceGroupPresentInfoKHR
p Ptr DeviceGroupPresentInfoKHR -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEVICE_GROUP_PRESENT_INFO_KHR)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceGroupPresentInfoKHR
p Ptr DeviceGroupPresentInfoKHR -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ ("pSwapchainImageCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceGroupPresentInfoKHR
p Ptr DeviceGroupPresentInfoKHR
-> Int -> "pSwapchainImageCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector Word32 -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Word32 -> Int) -> Vector Word32 -> Int
forall a b. (a -> b) -> a -> b
$ (Vector Word32
deviceMasks)) :: Word32))
    "pSwapchainImageCount" ::: Ptr Word32
pPDeviceMasks' <- ((("pSwapchainImageCount" ::: Ptr Word32) -> IO b) -> IO b)
-> ContT b IO ("pSwapchainImageCount" ::: Ptr Word32)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pSwapchainImageCount" ::: Ptr Word32) -> IO b) -> IO b)
 -> ContT b IO ("pSwapchainImageCount" ::: Ptr Word32))
-> ((("pSwapchainImageCount" ::: Ptr Word32) -> IO b) -> IO b)
-> ContT b IO ("pSwapchainImageCount" ::: Ptr Word32)
forall a b. (a -> b) -> a -> b
$ Int
-> Int -> (("pSwapchainImageCount" ::: Ptr Word32) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Word32 ((Vector Word32 -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Word32
deviceMasks)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 4) 4
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> Word32 -> IO ()) -> Vector Word32 -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Word32
e -> ("pSwapchainImageCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pSwapchainImageCount" ::: Ptr Word32
pPDeviceMasks' ("pSwapchainImageCount" ::: Ptr Word32)
-> Int -> "pSwapchainImageCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32) (Word32
e)) (Vector Word32
deviceMasks)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ("pSwapchainImageCount" ::: Ptr Word32)
-> ("pSwapchainImageCount" ::: Ptr Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceGroupPresentInfoKHR
p Ptr DeviceGroupPresentInfoKHR
-> Int -> Ptr ("pSwapchainImageCount" ::: Ptr Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr Word32))) ("pSwapchainImageCount" ::: Ptr Word32
pPDeviceMasks')
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceGroupPresentInfoKHR
p Ptr DeviceGroupPresentInfoKHR
-> Int
-> "pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr DeviceGroupPresentModeFlagBitsKHR)) ("modes" ::: DeviceGroupPresentModeFlagsKHR
mode)
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = 40
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr DeviceGroupPresentInfoKHR -> IO b -> IO b
pokeZeroCStruct p :: Ptr DeviceGroupPresentInfoKHR
p f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceGroupPresentInfoKHR
p Ptr DeviceGroupPresentInfoKHR -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEVICE_GROUP_PRESENT_INFO_KHR)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceGroupPresentInfoKHR
p Ptr DeviceGroupPresentInfoKHR -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    "pSwapchainImageCount" ::: Ptr Word32
pPDeviceMasks' <- ((("pSwapchainImageCount" ::: Ptr Word32) -> IO b) -> IO b)
-> ContT b IO ("pSwapchainImageCount" ::: Ptr Word32)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pSwapchainImageCount" ::: Ptr Word32) -> IO b) -> IO b)
 -> ContT b IO ("pSwapchainImageCount" ::: Ptr Word32))
-> ((("pSwapchainImageCount" ::: Ptr Word32) -> IO b) -> IO b)
-> ContT b IO ("pSwapchainImageCount" ::: Ptr Word32)
forall a b. (a -> b) -> a -> b
$ Int
-> Int -> (("pSwapchainImageCount" ::: Ptr Word32) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Word32 ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 4) 4
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> Word32 -> IO ()) -> Vector Word32 -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Word32
e -> ("pSwapchainImageCount" ::: Ptr Word32) -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pSwapchainImageCount" ::: Ptr Word32
pPDeviceMasks' ("pSwapchainImageCount" ::: Ptr Word32)
-> Int -> "pSwapchainImageCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32) (Word32
e)) (Vector Word32
forall a. Monoid a => a
mempty)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ("pSwapchainImageCount" ::: Ptr Word32)
-> ("pSwapchainImageCount" ::: Ptr Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceGroupPresentInfoKHR
p Ptr DeviceGroupPresentInfoKHR
-> Int -> Ptr ("pSwapchainImageCount" ::: Ptr Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr Word32))) ("pSwapchainImageCount" ::: Ptr Word32
pPDeviceMasks')
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceGroupPresentInfoKHR
p Ptr DeviceGroupPresentInfoKHR
-> Int
-> "pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr DeviceGroupPresentModeFlagBitsKHR)) ("modes" ::: DeviceGroupPresentModeFlagsKHR
forall a. Zero a => a
zero)
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f

instance FromCStruct DeviceGroupPresentInfoKHR where
  peekCStruct :: Ptr DeviceGroupPresentInfoKHR -> IO DeviceGroupPresentInfoKHR
peekCStruct p :: Ptr DeviceGroupPresentInfoKHR
p = do
    Word32
swapchainCount <- ("pSwapchainImageCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DeviceGroupPresentInfoKHR
p Ptr DeviceGroupPresentInfoKHR
-> Int -> "pSwapchainImageCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32))
    "pSwapchainImageCount" ::: Ptr Word32
pDeviceMasks <- Ptr ("pSwapchainImageCount" ::: Ptr Word32)
-> IO ("pSwapchainImageCount" ::: Ptr Word32)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr Word32) ((Ptr DeviceGroupPresentInfoKHR
p Ptr DeviceGroupPresentInfoKHR
-> Int -> Ptr ("pSwapchainImageCount" ::: Ptr Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr Word32)))
    Vector Word32
pDeviceMasks' <- Int -> (Int -> IO Word32) -> IO (Vector Word32)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
swapchainCount) (\i :: Int
i -> ("pSwapchainImageCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pSwapchainImageCount" ::: Ptr Word32
pDeviceMasks ("pSwapchainImageCount" ::: Ptr Word32)
-> Int -> "pSwapchainImageCount" ::: Ptr Word32
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32)))
    "modes" ::: DeviceGroupPresentModeFlagsKHR
mode <- ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall a. Storable a => Ptr a -> IO a
peek @DeviceGroupPresentModeFlagBitsKHR ((Ptr DeviceGroupPresentInfoKHR
p Ptr DeviceGroupPresentInfoKHR
-> Int
-> "pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr DeviceGroupPresentModeFlagBitsKHR))
    DeviceGroupPresentInfoKHR -> IO DeviceGroupPresentInfoKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DeviceGroupPresentInfoKHR -> IO DeviceGroupPresentInfoKHR)
-> DeviceGroupPresentInfoKHR -> IO DeviceGroupPresentInfoKHR
forall a b. (a -> b) -> a -> b
$ Vector Word32
-> ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> DeviceGroupPresentInfoKHR
DeviceGroupPresentInfoKHR
             Vector Word32
pDeviceMasks' "modes" ::: DeviceGroupPresentModeFlagsKHR
mode

instance Zero DeviceGroupPresentInfoKHR where
  zero :: DeviceGroupPresentInfoKHR
zero = Vector Word32
-> ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> DeviceGroupPresentInfoKHR
DeviceGroupPresentInfoKHR
           Vector Word32
forall a. Monoid a => a
mempty
           "modes" ::: DeviceGroupPresentModeFlagsKHR
forall a. Zero a => a
zero


-- | VkDeviceGroupSwapchainCreateInfoKHR - Structure specifying parameters of
-- a newly created swapchain object
--
-- = Description
--
-- If this structure is not present, @modes@ is considered to be
-- 'DEVICE_GROUP_PRESENT_MODE_LOCAL_BIT_KHR'.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'DeviceGroupPresentModeFlagsKHR',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data DeviceGroupSwapchainCreateInfoKHR = DeviceGroupSwapchainCreateInfoKHR
  { -- | @modes@ is a bitfield of modes that the swapchain /can/ be used with.
    --
    -- @modes@ /must/ be a valid combination of
    -- 'DeviceGroupPresentModeFlagBitsKHR' values
    --
    -- @modes@ /must/ not be @0@
    DeviceGroupSwapchainCreateInfoKHR
-> "modes" ::: DeviceGroupPresentModeFlagsKHR
modes :: DeviceGroupPresentModeFlagsKHR }
  deriving (Typeable, DeviceGroupSwapchainCreateInfoKHR
-> DeviceGroupSwapchainCreateInfoKHR -> Bool
(DeviceGroupSwapchainCreateInfoKHR
 -> DeviceGroupSwapchainCreateInfoKHR -> Bool)
-> (DeviceGroupSwapchainCreateInfoKHR
    -> DeviceGroupSwapchainCreateInfoKHR -> Bool)
-> Eq DeviceGroupSwapchainCreateInfoKHR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeviceGroupSwapchainCreateInfoKHR
-> DeviceGroupSwapchainCreateInfoKHR -> Bool
$c/= :: DeviceGroupSwapchainCreateInfoKHR
-> DeviceGroupSwapchainCreateInfoKHR -> Bool
== :: DeviceGroupSwapchainCreateInfoKHR
-> DeviceGroupSwapchainCreateInfoKHR -> Bool
$c== :: DeviceGroupSwapchainCreateInfoKHR
-> DeviceGroupSwapchainCreateInfoKHR -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DeviceGroupSwapchainCreateInfoKHR)
#endif
deriving instance Show DeviceGroupSwapchainCreateInfoKHR

instance ToCStruct DeviceGroupSwapchainCreateInfoKHR where
  withCStruct :: DeviceGroupSwapchainCreateInfoKHR
-> (Ptr DeviceGroupSwapchainCreateInfoKHR -> IO b) -> IO b
withCStruct x :: DeviceGroupSwapchainCreateInfoKHR
x f :: Ptr DeviceGroupSwapchainCreateInfoKHR -> IO b
f = Int
-> Int -> (Ptr DeviceGroupSwapchainCreateInfoKHR -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr DeviceGroupSwapchainCreateInfoKHR -> IO b) -> IO b)
-> (Ptr DeviceGroupSwapchainCreateInfoKHR -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr DeviceGroupSwapchainCreateInfoKHR
p -> Ptr DeviceGroupSwapchainCreateInfoKHR
-> DeviceGroupSwapchainCreateInfoKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DeviceGroupSwapchainCreateInfoKHR
p DeviceGroupSwapchainCreateInfoKHR
x (Ptr DeviceGroupSwapchainCreateInfoKHR -> IO b
f Ptr DeviceGroupSwapchainCreateInfoKHR
p)
  pokeCStruct :: Ptr DeviceGroupSwapchainCreateInfoKHR
-> DeviceGroupSwapchainCreateInfoKHR -> IO b -> IO b
pokeCStruct p :: Ptr DeviceGroupSwapchainCreateInfoKHR
p DeviceGroupSwapchainCreateInfoKHR{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceGroupSwapchainCreateInfoKHR
p Ptr DeviceGroupSwapchainCreateInfoKHR -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEVICE_GROUP_SWAPCHAIN_CREATE_INFO_KHR)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceGroupSwapchainCreateInfoKHR
p Ptr DeviceGroupSwapchainCreateInfoKHR -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceGroupSwapchainCreateInfoKHR
p Ptr DeviceGroupSwapchainCreateInfoKHR
-> Int
-> "pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceGroupPresentModeFlagsKHR)) ("modes" ::: DeviceGroupPresentModeFlagsKHR
modes)
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr DeviceGroupSwapchainCreateInfoKHR -> IO b -> IO b
pokeZeroCStruct p :: Ptr DeviceGroupSwapchainCreateInfoKHR
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceGroupSwapchainCreateInfoKHR
p Ptr DeviceGroupSwapchainCreateInfoKHR -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEVICE_GROUP_SWAPCHAIN_CREATE_INFO_KHR)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceGroupSwapchainCreateInfoKHR
p Ptr DeviceGroupSwapchainCreateInfoKHR -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceGroupSwapchainCreateInfoKHR
p Ptr DeviceGroupSwapchainCreateInfoKHR
-> Int
-> "pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceGroupPresentModeFlagsKHR)) ("modes" ::: DeviceGroupPresentModeFlagsKHR
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct DeviceGroupSwapchainCreateInfoKHR where
  peekCStruct :: Ptr DeviceGroupSwapchainCreateInfoKHR
-> IO DeviceGroupSwapchainCreateInfoKHR
peekCStruct p :: Ptr DeviceGroupSwapchainCreateInfoKHR
p = do
    "modes" ::: DeviceGroupPresentModeFlagsKHR
modes <- ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall a. Storable a => Ptr a -> IO a
peek @DeviceGroupPresentModeFlagsKHR ((Ptr DeviceGroupSwapchainCreateInfoKHR
p Ptr DeviceGroupSwapchainCreateInfoKHR
-> Int
-> "pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceGroupPresentModeFlagsKHR))
    DeviceGroupSwapchainCreateInfoKHR
-> IO DeviceGroupSwapchainCreateInfoKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DeviceGroupSwapchainCreateInfoKHR
 -> IO DeviceGroupSwapchainCreateInfoKHR)
-> DeviceGroupSwapchainCreateInfoKHR
-> IO DeviceGroupSwapchainCreateInfoKHR
forall a b. (a -> b) -> a -> b
$ ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> DeviceGroupSwapchainCreateInfoKHR
DeviceGroupSwapchainCreateInfoKHR
             "modes" ::: DeviceGroupPresentModeFlagsKHR
modes

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

instance Zero DeviceGroupSwapchainCreateInfoKHR where
  zero :: DeviceGroupSwapchainCreateInfoKHR
zero = ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> DeviceGroupSwapchainCreateInfoKHR
DeviceGroupSwapchainCreateInfoKHR
           "modes" ::: DeviceGroupPresentModeFlagsKHR
forall a. Zero a => a
zero


-- | VkDeviceGroupPresentModeFlagBitsKHR - Bitmask specifying supported
-- device group present modes
--
-- = See Also
--
-- 'DeviceGroupPresentInfoKHR', 'DeviceGroupPresentModeFlagsKHR'
newtype DeviceGroupPresentModeFlagBitsKHR = DeviceGroupPresentModeFlagBitsKHR Flags
  deriving newtype (("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Bool
(("modes" ::: DeviceGroupPresentModeFlagsKHR)
 -> ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Bool)
-> (("modes" ::: DeviceGroupPresentModeFlagsKHR)
    -> ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Bool)
-> Eq ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Bool
$c/= :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Bool
== :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Bool
$c== :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Bool
Eq, Eq ("modes" ::: DeviceGroupPresentModeFlagsKHR)
Eq ("modes" ::: DeviceGroupPresentModeFlagsKHR) =>
(("modes" ::: DeviceGroupPresentModeFlagsKHR)
 -> ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Ordering)
-> (("modes" ::: DeviceGroupPresentModeFlagsKHR)
    -> ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Bool)
-> (("modes" ::: DeviceGroupPresentModeFlagsKHR)
    -> ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Bool)
-> (("modes" ::: DeviceGroupPresentModeFlagsKHR)
    -> ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Bool)
-> (("modes" ::: DeviceGroupPresentModeFlagsKHR)
    -> ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Bool)
-> (("modes" ::: DeviceGroupPresentModeFlagsKHR)
    -> ("modes" ::: DeviceGroupPresentModeFlagsKHR)
    -> "modes" ::: DeviceGroupPresentModeFlagsKHR)
-> (("modes" ::: DeviceGroupPresentModeFlagsKHR)
    -> ("modes" ::: DeviceGroupPresentModeFlagsKHR)
    -> "modes" ::: DeviceGroupPresentModeFlagsKHR)
-> Ord ("modes" ::: DeviceGroupPresentModeFlagsKHR)
("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Bool
("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Ordering
("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> "modes" ::: DeviceGroupPresentModeFlagsKHR
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 :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> "modes" ::: DeviceGroupPresentModeFlagsKHR
$cmin :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> "modes" ::: DeviceGroupPresentModeFlagsKHR
max :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> "modes" ::: DeviceGroupPresentModeFlagsKHR
$cmax :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> "modes" ::: DeviceGroupPresentModeFlagsKHR
>= :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Bool
$c>= :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Bool
> :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Bool
$c> :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Bool
<= :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Bool
$c<= :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Bool
< :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Bool
$c< :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Bool
compare :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Ordering
$ccompare :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Ordering
$cp1Ord :: Eq ("modes" ::: DeviceGroupPresentModeFlagsKHR)
Ord, Ptr b -> Int -> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR)
Ptr b
-> Int -> ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> IO ()
("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR)
("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> Int -> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR)
("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> Int -> ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> IO ()
("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> IO ()
("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Int
(("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Int)
-> (("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Int)
-> (("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
    -> Int -> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> (("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
    -> Int -> ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> IO ())
-> (forall b.
    Ptr b -> Int -> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> (forall b.
    Ptr b
    -> Int -> ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> IO ())
-> (("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
    -> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> (("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
    -> ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> IO ())
-> Storable ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall b.
Ptr b -> Int -> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall b.
Ptr b
-> Int -> ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> 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 :: ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> IO ()
$cpoke :: ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> IO ()
peek :: ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR)
$cpeek :: ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR)
pokeByteOff :: Ptr b
-> Int -> ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> IO ()
$cpokeByteOff :: forall b.
Ptr b
-> Int -> ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> IO ()
peekByteOff :: Ptr b -> Int -> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR)
$cpeekByteOff :: forall b.
Ptr b -> Int -> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR)
pokeElemOff :: ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> Int -> ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> IO ()
$cpokeElemOff :: ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> Int -> ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> IO ()
peekElemOff :: ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> Int -> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR)
$cpeekElemOff :: ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> Int -> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR)
alignment :: ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Int
$calignment :: ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Int
sizeOf :: ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Int
$csizeOf :: ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Int
Storable, "modes" ::: DeviceGroupPresentModeFlagsKHR
("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> Zero ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall a. a -> Zero a
zero :: "modes" ::: DeviceGroupPresentModeFlagsKHR
$czero :: "modes" ::: DeviceGroupPresentModeFlagsKHR
Zero, Eq ("modes" ::: DeviceGroupPresentModeFlagsKHR)
"modes" ::: DeviceGroupPresentModeFlagsKHR
Eq ("modes" ::: DeviceGroupPresentModeFlagsKHR) =>
(("modes" ::: DeviceGroupPresentModeFlagsKHR)
 -> ("modes" ::: DeviceGroupPresentModeFlagsKHR)
 -> "modes" ::: DeviceGroupPresentModeFlagsKHR)
-> (("modes" ::: DeviceGroupPresentModeFlagsKHR)
    -> ("modes" ::: DeviceGroupPresentModeFlagsKHR)
    -> "modes" ::: DeviceGroupPresentModeFlagsKHR)
-> (("modes" ::: DeviceGroupPresentModeFlagsKHR)
    -> ("modes" ::: DeviceGroupPresentModeFlagsKHR)
    -> "modes" ::: DeviceGroupPresentModeFlagsKHR)
-> (("modes" ::: DeviceGroupPresentModeFlagsKHR)
    -> "modes" ::: DeviceGroupPresentModeFlagsKHR)
-> (("modes" ::: DeviceGroupPresentModeFlagsKHR)
    -> Int -> "modes" ::: DeviceGroupPresentModeFlagsKHR)
-> (("modes" ::: DeviceGroupPresentModeFlagsKHR)
    -> Int -> "modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> (Int -> "modes" ::: DeviceGroupPresentModeFlagsKHR)
-> (("modes" ::: DeviceGroupPresentModeFlagsKHR)
    -> Int -> "modes" ::: DeviceGroupPresentModeFlagsKHR)
-> (("modes" ::: DeviceGroupPresentModeFlagsKHR)
    -> Int -> "modes" ::: DeviceGroupPresentModeFlagsKHR)
-> (("modes" ::: DeviceGroupPresentModeFlagsKHR)
    -> Int -> "modes" ::: DeviceGroupPresentModeFlagsKHR)
-> (("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Int -> Bool)
-> (("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Maybe Int)
-> (("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Int)
-> (("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Bool)
-> (("modes" ::: DeviceGroupPresentModeFlagsKHR)
    -> Int -> "modes" ::: DeviceGroupPresentModeFlagsKHR)
-> (("modes" ::: DeviceGroupPresentModeFlagsKHR)
    -> Int -> "modes" ::: DeviceGroupPresentModeFlagsKHR)
-> (("modes" ::: DeviceGroupPresentModeFlagsKHR)
    -> Int -> "modes" ::: DeviceGroupPresentModeFlagsKHR)
-> (("modes" ::: DeviceGroupPresentModeFlagsKHR)
    -> Int -> "modes" ::: DeviceGroupPresentModeFlagsKHR)
-> (("modes" ::: DeviceGroupPresentModeFlagsKHR)
    -> Int -> "modes" ::: DeviceGroupPresentModeFlagsKHR)
-> (("modes" ::: DeviceGroupPresentModeFlagsKHR)
    -> Int -> "modes" ::: DeviceGroupPresentModeFlagsKHR)
-> (("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Int)
-> Bits ("modes" ::: DeviceGroupPresentModeFlagsKHR)
Int -> "modes" ::: DeviceGroupPresentModeFlagsKHR
("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Bool
("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Int
("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Maybe Int
("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> "modes" ::: DeviceGroupPresentModeFlagsKHR
("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Int -> Bool
("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> Int -> "modes" ::: DeviceGroupPresentModeFlagsKHR
("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> "modes" ::: DeviceGroupPresentModeFlagsKHR
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 :: ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Int
$cpopCount :: ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Int
rotateR :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> Int -> "modes" ::: DeviceGroupPresentModeFlagsKHR
$crotateR :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> Int -> "modes" ::: DeviceGroupPresentModeFlagsKHR
rotateL :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> Int -> "modes" ::: DeviceGroupPresentModeFlagsKHR
$crotateL :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> Int -> "modes" ::: DeviceGroupPresentModeFlagsKHR
unsafeShiftR :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> Int -> "modes" ::: DeviceGroupPresentModeFlagsKHR
$cunsafeShiftR :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> Int -> "modes" ::: DeviceGroupPresentModeFlagsKHR
shiftR :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> Int -> "modes" ::: DeviceGroupPresentModeFlagsKHR
$cshiftR :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> Int -> "modes" ::: DeviceGroupPresentModeFlagsKHR
unsafeShiftL :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> Int -> "modes" ::: DeviceGroupPresentModeFlagsKHR
$cunsafeShiftL :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> Int -> "modes" ::: DeviceGroupPresentModeFlagsKHR
shiftL :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> Int -> "modes" ::: DeviceGroupPresentModeFlagsKHR
$cshiftL :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> Int -> "modes" ::: DeviceGroupPresentModeFlagsKHR
isSigned :: ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Bool
$cisSigned :: ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Bool
bitSize :: ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Int
$cbitSize :: ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Int
bitSizeMaybe :: ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Maybe Int
$cbitSizeMaybe :: ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Maybe Int
testBit :: ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Int -> Bool
$ctestBit :: ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Int -> Bool
complementBit :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> Int -> "modes" ::: DeviceGroupPresentModeFlagsKHR
$ccomplementBit :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> Int -> "modes" ::: DeviceGroupPresentModeFlagsKHR
clearBit :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> Int -> "modes" ::: DeviceGroupPresentModeFlagsKHR
$cclearBit :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> Int -> "modes" ::: DeviceGroupPresentModeFlagsKHR
setBit :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> Int -> "modes" ::: DeviceGroupPresentModeFlagsKHR
$csetBit :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> Int -> "modes" ::: DeviceGroupPresentModeFlagsKHR
bit :: Int -> "modes" ::: DeviceGroupPresentModeFlagsKHR
$cbit :: Int -> "modes" ::: DeviceGroupPresentModeFlagsKHR
zeroBits :: "modes" ::: DeviceGroupPresentModeFlagsKHR
$czeroBits :: "modes" ::: DeviceGroupPresentModeFlagsKHR
rotate :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> Int -> "modes" ::: DeviceGroupPresentModeFlagsKHR
$crotate :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> Int -> "modes" ::: DeviceGroupPresentModeFlagsKHR
shift :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> Int -> "modes" ::: DeviceGroupPresentModeFlagsKHR
$cshift :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> Int -> "modes" ::: DeviceGroupPresentModeFlagsKHR
complement :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> "modes" ::: DeviceGroupPresentModeFlagsKHR
$ccomplement :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> "modes" ::: DeviceGroupPresentModeFlagsKHR
xor :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> "modes" ::: DeviceGroupPresentModeFlagsKHR
$cxor :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> "modes" ::: DeviceGroupPresentModeFlagsKHR
.|. :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> "modes" ::: DeviceGroupPresentModeFlagsKHR
$c.|. :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> "modes" ::: DeviceGroupPresentModeFlagsKHR
.&. :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> "modes" ::: DeviceGroupPresentModeFlagsKHR
$c.&. :: ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> "modes" ::: DeviceGroupPresentModeFlagsKHR
$cp1Bits :: Eq ("modes" ::: DeviceGroupPresentModeFlagsKHR)
Bits)

-- | 'DEVICE_GROUP_PRESENT_MODE_LOCAL_BIT_KHR' specifies that any physical
-- device with a presentation engine /can/ present its own swapchain
-- images.
pattern $bDEVICE_GROUP_PRESENT_MODE_LOCAL_BIT_KHR :: "modes" ::: DeviceGroupPresentModeFlagsKHR
$mDEVICE_GROUP_PRESENT_MODE_LOCAL_BIT_KHR :: forall r.
("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> (Void# -> r) -> (Void# -> r) -> r
DEVICE_GROUP_PRESENT_MODE_LOCAL_BIT_KHR = DeviceGroupPresentModeFlagBitsKHR 0x00000001
-- | 'DEVICE_GROUP_PRESENT_MODE_REMOTE_BIT_KHR' specifies that any physical
-- device with a presentation engine /can/ present swapchain images from
-- any physical device in its @presentMask@.
pattern $bDEVICE_GROUP_PRESENT_MODE_REMOTE_BIT_KHR :: "modes" ::: DeviceGroupPresentModeFlagsKHR
$mDEVICE_GROUP_PRESENT_MODE_REMOTE_BIT_KHR :: forall r.
("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> (Void# -> r) -> (Void# -> r) -> r
DEVICE_GROUP_PRESENT_MODE_REMOTE_BIT_KHR = DeviceGroupPresentModeFlagBitsKHR 0x00000002
-- | 'DEVICE_GROUP_PRESENT_MODE_SUM_BIT_KHR' specifies that any physical
-- device with a presentation engine /can/ present the sum of swapchain
-- images from any physical devices in its @presentMask@.
pattern $bDEVICE_GROUP_PRESENT_MODE_SUM_BIT_KHR :: "modes" ::: DeviceGroupPresentModeFlagsKHR
$mDEVICE_GROUP_PRESENT_MODE_SUM_BIT_KHR :: forall r.
("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> (Void# -> r) -> (Void# -> r) -> r
DEVICE_GROUP_PRESENT_MODE_SUM_BIT_KHR = DeviceGroupPresentModeFlagBitsKHR 0x00000004
-- | 'DEVICE_GROUP_PRESENT_MODE_LOCAL_MULTI_DEVICE_BIT_KHR' specifies that
-- multiple physical devices with a presentation engine /can/ each present
-- their own swapchain images.
pattern $bDEVICE_GROUP_PRESENT_MODE_LOCAL_MULTI_DEVICE_BIT_KHR :: "modes" ::: DeviceGroupPresentModeFlagsKHR
$mDEVICE_GROUP_PRESENT_MODE_LOCAL_MULTI_DEVICE_BIT_KHR :: forall r.
("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> (Void# -> r) -> (Void# -> r) -> r
DEVICE_GROUP_PRESENT_MODE_LOCAL_MULTI_DEVICE_BIT_KHR = DeviceGroupPresentModeFlagBitsKHR 0x00000008

type DeviceGroupPresentModeFlagsKHR = DeviceGroupPresentModeFlagBitsKHR

instance Show DeviceGroupPresentModeFlagBitsKHR where
  showsPrec :: Int -> ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> ShowS
showsPrec p :: Int
p = \case
    DEVICE_GROUP_PRESENT_MODE_LOCAL_BIT_KHR -> String -> ShowS
showString "DEVICE_GROUP_PRESENT_MODE_LOCAL_BIT_KHR"
    DEVICE_GROUP_PRESENT_MODE_REMOTE_BIT_KHR -> String -> ShowS
showString "DEVICE_GROUP_PRESENT_MODE_REMOTE_BIT_KHR"
    DEVICE_GROUP_PRESENT_MODE_SUM_BIT_KHR -> String -> ShowS
showString "DEVICE_GROUP_PRESENT_MODE_SUM_BIT_KHR"
    DEVICE_GROUP_PRESENT_MODE_LOCAL_MULTI_DEVICE_BIT_KHR -> String -> ShowS
showString "DEVICE_GROUP_PRESENT_MODE_LOCAL_MULTI_DEVICE_BIT_KHR"
    DeviceGroupPresentModeFlagBitsKHR x :: Word32
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "DeviceGroupPresentModeFlagBitsKHR 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word32 -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex Word32
x)

instance Read DeviceGroupPresentModeFlagBitsKHR where
  readPrec :: ReadPrec ("modes" ::: DeviceGroupPresentModeFlagsKHR)
readPrec = ReadPrec ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ReadPrec ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec ("modes" ::: DeviceGroupPresentModeFlagsKHR))]
-> ReadPrec ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("DEVICE_GROUP_PRESENT_MODE_LOCAL_BIT_KHR", ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ReadPrec ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall (f :: * -> *) a. Applicative f => a -> f a
pure "modes" ::: DeviceGroupPresentModeFlagsKHR
DEVICE_GROUP_PRESENT_MODE_LOCAL_BIT_KHR)
                            , ("DEVICE_GROUP_PRESENT_MODE_REMOTE_BIT_KHR", ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ReadPrec ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall (f :: * -> *) a. Applicative f => a -> f a
pure "modes" ::: DeviceGroupPresentModeFlagsKHR
DEVICE_GROUP_PRESENT_MODE_REMOTE_BIT_KHR)
                            , ("DEVICE_GROUP_PRESENT_MODE_SUM_BIT_KHR", ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ReadPrec ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall (f :: * -> *) a. Applicative f => a -> f a
pure "modes" ::: DeviceGroupPresentModeFlagsKHR
DEVICE_GROUP_PRESENT_MODE_SUM_BIT_KHR)
                            , ("DEVICE_GROUP_PRESENT_MODE_LOCAL_MULTI_DEVICE_BIT_KHR", ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ReadPrec ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall (f :: * -> *) a. Applicative f => a -> f a
pure "modes" ::: DeviceGroupPresentModeFlagsKHR
DEVICE_GROUP_PRESENT_MODE_LOCAL_MULTI_DEVICE_BIT_KHR)]
                     ReadPrec ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ReadPrec ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ReadPrec ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                     Int
-> ReadPrec ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ReadPrec ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
                       Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "DeviceGroupPresentModeFlagBitsKHR")
                       Word32
v <- ReadPrec Word32 -> ReadPrec Word32
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Word32
forall a. Read a => ReadPrec a
readPrec
                       ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ReadPrec ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Word32 -> "modes" ::: DeviceGroupPresentModeFlagsKHR
DeviceGroupPresentModeFlagBitsKHR Word32
v)))


-- | VkSwapchainCreateFlagBitsKHR - Bitmask controlling swapchain creation
--
-- = See Also
--
-- 'SwapchainCreateFlagsKHR'
newtype SwapchainCreateFlagBitsKHR = SwapchainCreateFlagBitsKHR Flags
  deriving newtype (SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR -> Bool
(SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR -> Bool)
-> (SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR -> Bool)
-> Eq SwapchainCreateFlagsKHR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR -> Bool
$c/= :: SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR -> Bool
== :: SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR -> Bool
$c== :: SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR -> Bool
Eq, Eq SwapchainCreateFlagsKHR
Eq SwapchainCreateFlagsKHR =>
(SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR -> Ordering)
-> (SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR -> Bool)
-> (SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR -> Bool)
-> (SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR -> Bool)
-> (SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR -> Bool)
-> (SwapchainCreateFlagsKHR
    -> SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR)
-> (SwapchainCreateFlagsKHR
    -> SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR)
-> Ord SwapchainCreateFlagsKHR
SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR -> Bool
SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR -> Ordering
SwapchainCreateFlagsKHR
-> SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR
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 :: SwapchainCreateFlagsKHR
-> SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR
$cmin :: SwapchainCreateFlagsKHR
-> SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR
max :: SwapchainCreateFlagsKHR
-> SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR
$cmax :: SwapchainCreateFlagsKHR
-> SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR
>= :: SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR -> Bool
$c>= :: SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR -> Bool
> :: SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR -> Bool
$c> :: SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR -> Bool
<= :: SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR -> Bool
$c<= :: SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR -> Bool
< :: SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR -> Bool
$c< :: SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR -> Bool
compare :: SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR -> Ordering
$ccompare :: SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR -> Ordering
$cp1Ord :: Eq SwapchainCreateFlagsKHR
Ord, Ptr b -> Int -> IO SwapchainCreateFlagsKHR
Ptr b -> Int -> SwapchainCreateFlagsKHR -> IO ()
Ptr SwapchainCreateFlagsKHR -> IO SwapchainCreateFlagsKHR
Ptr SwapchainCreateFlagsKHR -> Int -> IO SwapchainCreateFlagsKHR
Ptr SwapchainCreateFlagsKHR
-> Int -> SwapchainCreateFlagsKHR -> IO ()
Ptr SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR -> IO ()
SwapchainCreateFlagsKHR -> Int
(SwapchainCreateFlagsKHR -> Int)
-> (SwapchainCreateFlagsKHR -> Int)
-> (Ptr SwapchainCreateFlagsKHR
    -> Int -> IO SwapchainCreateFlagsKHR)
-> (Ptr SwapchainCreateFlagsKHR
    -> Int -> SwapchainCreateFlagsKHR -> IO ())
-> (forall b. Ptr b -> Int -> IO SwapchainCreateFlagsKHR)
-> (forall b. Ptr b -> Int -> SwapchainCreateFlagsKHR -> IO ())
-> (Ptr SwapchainCreateFlagsKHR -> IO SwapchainCreateFlagsKHR)
-> (Ptr SwapchainCreateFlagsKHR
    -> SwapchainCreateFlagsKHR -> IO ())
-> Storable SwapchainCreateFlagsKHR
forall b. Ptr b -> Int -> IO SwapchainCreateFlagsKHR
forall b. Ptr b -> Int -> SwapchainCreateFlagsKHR -> 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 SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR -> IO ()
$cpoke :: Ptr SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR -> IO ()
peek :: Ptr SwapchainCreateFlagsKHR -> IO SwapchainCreateFlagsKHR
$cpeek :: Ptr SwapchainCreateFlagsKHR -> IO SwapchainCreateFlagsKHR
pokeByteOff :: Ptr b -> Int -> SwapchainCreateFlagsKHR -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> SwapchainCreateFlagsKHR -> IO ()
peekByteOff :: Ptr b -> Int -> IO SwapchainCreateFlagsKHR
$cpeekByteOff :: forall b. Ptr b -> Int -> IO SwapchainCreateFlagsKHR
pokeElemOff :: Ptr SwapchainCreateFlagsKHR
-> Int -> SwapchainCreateFlagsKHR -> IO ()
$cpokeElemOff :: Ptr SwapchainCreateFlagsKHR
-> Int -> SwapchainCreateFlagsKHR -> IO ()
peekElemOff :: Ptr SwapchainCreateFlagsKHR -> Int -> IO SwapchainCreateFlagsKHR
$cpeekElemOff :: Ptr SwapchainCreateFlagsKHR -> Int -> IO SwapchainCreateFlagsKHR
alignment :: SwapchainCreateFlagsKHR -> Int
$calignment :: SwapchainCreateFlagsKHR -> Int
sizeOf :: SwapchainCreateFlagsKHR -> Int
$csizeOf :: SwapchainCreateFlagsKHR -> Int
Storable, SwapchainCreateFlagsKHR
SwapchainCreateFlagsKHR -> Zero SwapchainCreateFlagsKHR
forall a. a -> Zero a
zero :: SwapchainCreateFlagsKHR
$czero :: SwapchainCreateFlagsKHR
Zero, Eq SwapchainCreateFlagsKHR
SwapchainCreateFlagsKHR
Eq SwapchainCreateFlagsKHR =>
(SwapchainCreateFlagsKHR
 -> SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR)
-> (SwapchainCreateFlagsKHR
    -> SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR)
-> (SwapchainCreateFlagsKHR
    -> SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR)
-> (SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR)
-> (SwapchainCreateFlagsKHR -> Int -> SwapchainCreateFlagsKHR)
-> (SwapchainCreateFlagsKHR -> Int -> SwapchainCreateFlagsKHR)
-> SwapchainCreateFlagsKHR
-> (Int -> SwapchainCreateFlagsKHR)
-> (SwapchainCreateFlagsKHR -> Int -> SwapchainCreateFlagsKHR)
-> (SwapchainCreateFlagsKHR -> Int -> SwapchainCreateFlagsKHR)
-> (SwapchainCreateFlagsKHR -> Int -> SwapchainCreateFlagsKHR)
-> (SwapchainCreateFlagsKHR -> Int -> Bool)
-> (SwapchainCreateFlagsKHR -> Maybe Int)
-> (SwapchainCreateFlagsKHR -> Int)
-> (SwapchainCreateFlagsKHR -> Bool)
-> (SwapchainCreateFlagsKHR -> Int -> SwapchainCreateFlagsKHR)
-> (SwapchainCreateFlagsKHR -> Int -> SwapchainCreateFlagsKHR)
-> (SwapchainCreateFlagsKHR -> Int -> SwapchainCreateFlagsKHR)
-> (SwapchainCreateFlagsKHR -> Int -> SwapchainCreateFlagsKHR)
-> (SwapchainCreateFlagsKHR -> Int -> SwapchainCreateFlagsKHR)
-> (SwapchainCreateFlagsKHR -> Int -> SwapchainCreateFlagsKHR)
-> (SwapchainCreateFlagsKHR -> Int)
-> Bits SwapchainCreateFlagsKHR
Int -> SwapchainCreateFlagsKHR
SwapchainCreateFlagsKHR -> Bool
SwapchainCreateFlagsKHR -> Int
SwapchainCreateFlagsKHR -> Maybe Int
SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR
SwapchainCreateFlagsKHR -> Int -> Bool
SwapchainCreateFlagsKHR -> Int -> SwapchainCreateFlagsKHR
SwapchainCreateFlagsKHR
-> SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR
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 :: SwapchainCreateFlagsKHR -> Int
$cpopCount :: SwapchainCreateFlagsKHR -> Int
rotateR :: SwapchainCreateFlagsKHR -> Int -> SwapchainCreateFlagsKHR
$crotateR :: SwapchainCreateFlagsKHR -> Int -> SwapchainCreateFlagsKHR
rotateL :: SwapchainCreateFlagsKHR -> Int -> SwapchainCreateFlagsKHR
$crotateL :: SwapchainCreateFlagsKHR -> Int -> SwapchainCreateFlagsKHR
unsafeShiftR :: SwapchainCreateFlagsKHR -> Int -> SwapchainCreateFlagsKHR
$cunsafeShiftR :: SwapchainCreateFlagsKHR -> Int -> SwapchainCreateFlagsKHR
shiftR :: SwapchainCreateFlagsKHR -> Int -> SwapchainCreateFlagsKHR
$cshiftR :: SwapchainCreateFlagsKHR -> Int -> SwapchainCreateFlagsKHR
unsafeShiftL :: SwapchainCreateFlagsKHR -> Int -> SwapchainCreateFlagsKHR
$cunsafeShiftL :: SwapchainCreateFlagsKHR -> Int -> SwapchainCreateFlagsKHR
shiftL :: SwapchainCreateFlagsKHR -> Int -> SwapchainCreateFlagsKHR
$cshiftL :: SwapchainCreateFlagsKHR -> Int -> SwapchainCreateFlagsKHR
isSigned :: SwapchainCreateFlagsKHR -> Bool
$cisSigned :: SwapchainCreateFlagsKHR -> Bool
bitSize :: SwapchainCreateFlagsKHR -> Int
$cbitSize :: SwapchainCreateFlagsKHR -> Int
bitSizeMaybe :: SwapchainCreateFlagsKHR -> Maybe Int
$cbitSizeMaybe :: SwapchainCreateFlagsKHR -> Maybe Int
testBit :: SwapchainCreateFlagsKHR -> Int -> Bool
$ctestBit :: SwapchainCreateFlagsKHR -> Int -> Bool
complementBit :: SwapchainCreateFlagsKHR -> Int -> SwapchainCreateFlagsKHR
$ccomplementBit :: SwapchainCreateFlagsKHR -> Int -> SwapchainCreateFlagsKHR
clearBit :: SwapchainCreateFlagsKHR -> Int -> SwapchainCreateFlagsKHR
$cclearBit :: SwapchainCreateFlagsKHR -> Int -> SwapchainCreateFlagsKHR
setBit :: SwapchainCreateFlagsKHR -> Int -> SwapchainCreateFlagsKHR
$csetBit :: SwapchainCreateFlagsKHR -> Int -> SwapchainCreateFlagsKHR
bit :: Int -> SwapchainCreateFlagsKHR
$cbit :: Int -> SwapchainCreateFlagsKHR
zeroBits :: SwapchainCreateFlagsKHR
$czeroBits :: SwapchainCreateFlagsKHR
rotate :: SwapchainCreateFlagsKHR -> Int -> SwapchainCreateFlagsKHR
$crotate :: SwapchainCreateFlagsKHR -> Int -> SwapchainCreateFlagsKHR
shift :: SwapchainCreateFlagsKHR -> Int -> SwapchainCreateFlagsKHR
$cshift :: SwapchainCreateFlagsKHR -> Int -> SwapchainCreateFlagsKHR
complement :: SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR
$ccomplement :: SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR
xor :: SwapchainCreateFlagsKHR
-> SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR
$cxor :: SwapchainCreateFlagsKHR
-> SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR
.|. :: SwapchainCreateFlagsKHR
-> SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR
$c.|. :: SwapchainCreateFlagsKHR
-> SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR
.&. :: SwapchainCreateFlagsKHR
-> SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR
$c.&. :: SwapchainCreateFlagsKHR
-> SwapchainCreateFlagsKHR -> SwapchainCreateFlagsKHR
$cp1Bits :: Eq SwapchainCreateFlagsKHR
Bits)

-- | 'SWAPCHAIN_CREATE_MUTABLE_FORMAT_BIT_KHR' specifies that the images of
-- the swapchain /can/ be used to create a
-- 'Vulkan.Core10.Handles.ImageView' with a different format than what the
-- swapchain was created with. The list of allowed image view formats are
-- specified by adding a
-- 'Vulkan.Core12.Promoted_From_VK_KHR_image_format_list.ImageFormatListCreateInfo'
-- structure to the @pNext@ chain of 'SwapchainCreateInfoKHR'. In addition,
-- this flag also specifies that the swapchain /can/ be created with usage
-- flags that are not supported for the format the swapchain is created
-- with but are supported for at least one of the allowed image view
-- formats.
pattern $bSWAPCHAIN_CREATE_MUTABLE_FORMAT_BIT_KHR :: SwapchainCreateFlagsKHR
$mSWAPCHAIN_CREATE_MUTABLE_FORMAT_BIT_KHR :: forall r.
SwapchainCreateFlagsKHR -> (Void# -> r) -> (Void# -> r) -> r
SWAPCHAIN_CREATE_MUTABLE_FORMAT_BIT_KHR = SwapchainCreateFlagBitsKHR 0x00000004
-- | 'SWAPCHAIN_CREATE_SPLIT_INSTANCE_BIND_REGIONS_BIT_KHR' specifies that
-- images created from the swapchain (i.e. with the @swapchain@ member of
-- 'ImageSwapchainCreateInfoKHR' set to this swapchain’s handle) /must/ use
-- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SPLIT_INSTANCE_BIND_REGIONS_BIT'.
pattern $bSWAPCHAIN_CREATE_SPLIT_INSTANCE_BIND_REGIONS_BIT_KHR :: SwapchainCreateFlagsKHR
$mSWAPCHAIN_CREATE_SPLIT_INSTANCE_BIND_REGIONS_BIT_KHR :: forall r.
SwapchainCreateFlagsKHR -> (Void# -> r) -> (Void# -> r) -> r
SWAPCHAIN_CREATE_SPLIT_INSTANCE_BIND_REGIONS_BIT_KHR = SwapchainCreateFlagBitsKHR 0x00000001
-- | 'SWAPCHAIN_CREATE_PROTECTED_BIT_KHR' specifies that images created from
-- the swapchain are protected images.
pattern $bSWAPCHAIN_CREATE_PROTECTED_BIT_KHR :: SwapchainCreateFlagsKHR
$mSWAPCHAIN_CREATE_PROTECTED_BIT_KHR :: forall r.
SwapchainCreateFlagsKHR -> (Void# -> r) -> (Void# -> r) -> r
SWAPCHAIN_CREATE_PROTECTED_BIT_KHR = SwapchainCreateFlagBitsKHR 0x00000002

type SwapchainCreateFlagsKHR = SwapchainCreateFlagBitsKHR

instance Show SwapchainCreateFlagBitsKHR where
  showsPrec :: Int -> SwapchainCreateFlagsKHR -> ShowS
showsPrec p :: Int
p = \case
    SWAPCHAIN_CREATE_MUTABLE_FORMAT_BIT_KHR -> String -> ShowS
showString "SWAPCHAIN_CREATE_MUTABLE_FORMAT_BIT_KHR"
    SWAPCHAIN_CREATE_SPLIT_INSTANCE_BIND_REGIONS_BIT_KHR -> String -> ShowS
showString "SWAPCHAIN_CREATE_SPLIT_INSTANCE_BIND_REGIONS_BIT_KHR"
    SWAPCHAIN_CREATE_PROTECTED_BIT_KHR -> String -> ShowS
showString "SWAPCHAIN_CREATE_PROTECTED_BIT_KHR"
    SwapchainCreateFlagBitsKHR x :: Word32
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "SwapchainCreateFlagBitsKHR 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word32 -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex Word32
x)

instance Read SwapchainCreateFlagBitsKHR where
  readPrec :: ReadPrec SwapchainCreateFlagsKHR
readPrec = ReadPrec SwapchainCreateFlagsKHR
-> ReadPrec SwapchainCreateFlagsKHR
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec SwapchainCreateFlagsKHR)]
-> ReadPrec SwapchainCreateFlagsKHR
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("SWAPCHAIN_CREATE_MUTABLE_FORMAT_BIT_KHR", SwapchainCreateFlagsKHR -> ReadPrec SwapchainCreateFlagsKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure SwapchainCreateFlagsKHR
SWAPCHAIN_CREATE_MUTABLE_FORMAT_BIT_KHR)
                            , ("SWAPCHAIN_CREATE_SPLIT_INSTANCE_BIND_REGIONS_BIT_KHR", SwapchainCreateFlagsKHR -> ReadPrec SwapchainCreateFlagsKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure SwapchainCreateFlagsKHR
SWAPCHAIN_CREATE_SPLIT_INSTANCE_BIND_REGIONS_BIT_KHR)
                            , ("SWAPCHAIN_CREATE_PROTECTED_BIT_KHR", SwapchainCreateFlagsKHR -> ReadPrec SwapchainCreateFlagsKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure SwapchainCreateFlagsKHR
SWAPCHAIN_CREATE_PROTECTED_BIT_KHR)]
                     ReadPrec SwapchainCreateFlagsKHR
-> ReadPrec SwapchainCreateFlagsKHR
-> ReadPrec SwapchainCreateFlagsKHR
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                     Int
-> ReadPrec SwapchainCreateFlagsKHR
-> ReadPrec SwapchainCreateFlagsKHR
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
                       Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "SwapchainCreateFlagBitsKHR")
                       Word32
v <- ReadPrec Word32 -> ReadPrec Word32
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Word32
forall a. Read a => ReadPrec a
readPrec
                       SwapchainCreateFlagsKHR -> ReadPrec SwapchainCreateFlagsKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Word32 -> SwapchainCreateFlagsKHR
SwapchainCreateFlagBitsKHR Word32
v)))


type KHR_SWAPCHAIN_SPEC_VERSION = 70

-- No documentation found for TopLevel "VK_KHR_SWAPCHAIN_SPEC_VERSION"
pattern KHR_SWAPCHAIN_SPEC_VERSION :: forall a . Integral a => a
pattern $bKHR_SWAPCHAIN_SPEC_VERSION :: a
$mKHR_SWAPCHAIN_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
KHR_SWAPCHAIN_SPEC_VERSION = 70


type KHR_SWAPCHAIN_EXTENSION_NAME = "VK_KHR_swapchain"

-- No documentation found for TopLevel "VK_KHR_SWAPCHAIN_EXTENSION_NAME"
pattern KHR_SWAPCHAIN_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bKHR_SWAPCHAIN_EXTENSION_NAME :: a
$mKHR_SWAPCHAIN_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
KHR_SWAPCHAIN_EXTENSION_NAME = "VK_KHR_swapchain"