{-# 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(..)
                                           , DeviceGroupPresentModeFlagsKHR
                                           , 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
                                                                              , ..
                                                                              )
                                           , SwapchainCreateFlagsKHR
                                           , SwapchainCreateFlagBitsKHR( SWAPCHAIN_CREATE_MUTABLE_FORMAT_BIT_KHR
                                                                       , SWAPCHAIN_CREATE_SPLIT_INSTANCE_BIND_REGIONS_BIT_KHR
                                                                       , SWAPCHAIN_CREATE_PROTECTED_BIT_KHR
                                                                       , ..
                                                                       )
                                           , 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 Vulkan.Internal.Utils (enumReadPrec)
import Vulkan.Internal.Utils (enumShowsPrec)
import Vulkan.Internal.Utils (traceAroundEvent)
import Control.Exception.Base (bracket)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Data.Typeable (eqT)
import Foreign.Marshal.Alloc (allocaBytes)
import Foreign.Marshal.Alloc (callocBytes)
import Foreign.Marshal.Alloc (free)
import GHC.Base (when)
import GHC.IO (throwIO)
import GHC.Ptr (castPtr)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import GHC.Show (showString)
import Numeric (showHex)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import Data.Vector (generateM)
import qualified Data.Vector (imapM_)
import qualified Data.Vector (length)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero)
import Vulkan.Zero (Zero(..))
import Control.Monad.IO.Class (MonadIO)
import Data.Bits (Bits)
import Data.Bits (FiniteBits)
import Data.String (IsString)
import Data.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 GHC.Show (Show(showsPrec))
import Data.Word (Word32)
import Data.Word (Word64)
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.Core10.Handles (Device(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.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(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 {-# SOURCE #-} Vulkan.Extensions.VK_KHR_present_id (PresentIdKHR)
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(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.Exception (VulkanException(..))
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
createSwapchainKHR :: forall a io
                    . (Extendss SwapchainCreateInfoKHR a, PokeChain a, MonadIO io)
                   => 
                      Device
                   -> 
                      
                      (SwapchainCreateInfoKHR a)
                   -> 
                      
                      
                      ("allocator" ::: Maybe AllocationCallbacks)
                   -> io (SwapchainKHR)
createSwapchainKHR :: Device
-> SwapchainCreateInfoKHR a
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io SwapchainKHR
createSwapchainKHR Device
device SwapchainCreateInfoKHR a
createInfo "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 (case Device
device of Device{DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds :: DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  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 String
"" String
"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
    "allocator" ::: Maybe AllocationCallbacks
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 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 Int
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
$ String -> IO Result -> IO Result
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCreateSwapchainKHR" (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)
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 SwapchainCreateInfoKHR a
pCreateInfo "allocator" ::: Maybe AllocationCallbacks
pAllocator 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 ()
destroySwapchainKHR :: forall io
                     . (MonadIO io)
                    => 
                       
                       Device
                    -> 
                       SwapchainKHR
                    -> 
                       
                       
                       ("allocator" ::: Maybe AllocationCallbacks)
                    -> io ()
destroySwapchainKHR :: Device
-> SwapchainKHR
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ()
destroySwapchainKHR Device
device SwapchainKHR
swapchain "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 (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  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 String
"" String
"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
    "allocator" ::: Maybe AllocationCallbacks
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 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
$ String -> IO () -> IO ()
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkDestroySwapchainKHR" (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
getSwapchainImagesKHR :: forall io
                       . (MonadIO io)
                      => 
                         Device
                      -> 
                         SwapchainKHR
                      -> io (Result, ("swapchainImages" ::: Vector Image))
getSwapchainImagesKHR :: Device
-> SwapchainKHR -> io (Result, "swapchainImages" ::: Vector Image)
getSwapchainImagesKHR Device
device 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 (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  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 String
"" String
"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 Int
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
$ String -> IO Result -> IO Result
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkGetSwapchainImagesKHR" (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
* Int
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
$ String -> IO Result -> IO Result
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkGetSwapchainImagesKHR" (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')) (\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` (Int
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
acquireNextImageKHRSafeOrUnsafe :: forall io
                                 . (MonadIO io)
                                => (FunPtr (Ptr Device_T -> SwapchainKHR -> Word64 -> Semaphore -> Fence -> Ptr Word32 -> IO Result) -> Ptr Device_T -> SwapchainKHR -> Word64 -> Semaphore -> Fence -> Ptr Word32 -> IO Result)
                                -> 
                                   Device
                                -> 
                                   
                                   SwapchainKHR
                                -> 
                                   
                                   ("timeout" ::: Word64)
                                -> 
                                   
                                   Semaphore
                                -> 
                                   
                                   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 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 SwapchainKHR
swapchain Word64
timeout Semaphore
semaphore 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 (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  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 String
"" String
"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 Int
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
$ String -> IO Result -> IO Result
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkAcquireNextImageKHR" (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)
acquireNextImageKHR :: forall io
                     . (MonadIO io)
                    => 
                       Device
                    -> 
                       
                       SwapchainKHR
                    -> 
                       
                       ("timeout" ::: Word64)
                    -> 
                       
                       Semaphore
                    -> 
                       
                       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
acquireNextImageKHRSafe :: forall io
                         . (MonadIO io)
                        => 
                           Device
                        -> 
                           
                           SwapchainKHR
                        -> 
                           
                           ("timeout" ::: Word64)
                        -> 
                           
                           Semaphore
                        -> 
                           
                           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
queuePresentKHR :: forall a io
                 . (Extendss PresentInfoKHR a, PokeChain a, MonadIO io)
                => 
                   
                   Queue
                -> 
                   
                   (PresentInfoKHR a)
                -> io (Result)
queuePresentKHR :: Queue -> PresentInfoKHR a -> io Result
queuePresentKHR Queue
queue 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 (case Queue
queue of Queue{DeviceCmds
$sel:deviceCmds:Queue :: Queue -> DeviceCmds
deviceCmds :: DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  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 String
"" String
"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
$ String -> IO Result -> IO Result
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkQueuePresentKHR" (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
getDeviceGroupPresentCapabilitiesKHR :: forall io
                                      . (MonadIO io)
                                     => 
                                        
                                        
                                        
                                        Device
                                     -> io (DeviceGroupPresentCapabilitiesKHR)
getDeviceGroupPresentCapabilitiesKHR :: Device -> io DeviceGroupPresentCapabilitiesKHR
getDeviceGroupPresentCapabilitiesKHR 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 (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  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 String
"" String
"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
$ String -> IO Result -> IO Result
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkGetDeviceGroupPresentCapabilitiesKHR" (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
getDeviceGroupSurfacePresentModesKHR :: forall io
                                      . (MonadIO io)
                                     => 
                                        Device
                                     -> 
                                        SurfaceKHR
                                     -> io (("modes" ::: DeviceGroupPresentModeFlagsKHR))
getDeviceGroupSurfacePresentModesKHR :: Device
-> SurfaceKHR -> io ("modes" ::: DeviceGroupPresentModeFlagsKHR)
getDeviceGroupSurfacePresentModesKHR Device
device 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 (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  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 String
"" String
"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 Int
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
$ String -> IO Result -> IO Result
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkGetDeviceGroupSurfacePresentModesKHR" (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
acquireNextImage2KHRSafeOrUnsafe :: forall io
                                  . (MonadIO io)
                                 => (FunPtr (Ptr Device_T -> Ptr AcquireNextImageInfoKHR -> Ptr Word32 -> IO Result) -> Ptr Device_T -> Ptr AcquireNextImageInfoKHR -> Ptr Word32 -> IO Result)
                                 -> 
                                    Device
                                 -> 
                                    
                                    ("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 FunPtr
  (Ptr Device_T
   -> Ptr AcquireNextImageInfoKHR
   -> ("pSwapchainImageCount" ::: Ptr Word32)
   -> IO Result)
-> Ptr Device_T
-> Ptr AcquireNextImageInfoKHR
-> ("pSwapchainImageCount" ::: Ptr Word32)
-> IO Result
mkVkAcquireNextImage2KHR Device
device 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 (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  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 String
"" String
"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 Int
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
$ String -> IO Result -> IO Result
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkAcquireNextImage2KHR" (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)
acquireNextImage2KHR :: forall io
                      . (MonadIO io)
                     => 
                        Device
                     -> 
                        
                        ("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
acquireNextImage2KHRSafe :: forall io
                          . (MonadIO io)
                         => 
                            Device
                         -> 
                            
                            ("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
getPhysicalDevicePresentRectanglesKHR :: forall io
                                       . (MonadIO io)
                                      => 
                                         PhysicalDevice
                                      -> 
                                         SurfaceKHR
                                      -> io (Result, ("rects" ::: Vector Rect2D))
getPhysicalDevicePresentRectanglesKHR :: PhysicalDevice
-> SurfaceKHR -> io (Result, "rects" ::: Vector Rect2D)
getPhysicalDevicePresentRectanglesKHR PhysicalDevice
physicalDevice 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 (case PhysicalDevice
physicalDevice of PhysicalDevice{InstanceCmds
$sel:instanceCmds:PhysicalDevice :: PhysicalDevice -> InstanceCmds
instanceCmds :: InstanceCmds
instanceCmds} -> InstanceCmds
instanceCmds)
  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 String
"" String
"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 Int
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
$ String -> IO Result -> IO Result
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkGetPhysicalDevicePresentRectanglesKHR" (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
* Int
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 (\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
* Int
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
$ ())) [Int
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
- Int
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
$ String -> IO Result -> IO Result
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkGetPhysicalDevicePresentRectanglesKHR" (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')) (\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` (Int
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')
data SwapchainCreateInfoKHR (es :: [Type]) = SwapchainCreateInfoKHR
  { 
    SwapchainCreateInfoKHR es -> Chain es
next :: Chain es
  , 
    
    SwapchainCreateInfoKHR es -> SwapchainCreateFlagsKHR
flags :: SwapchainCreateFlagsKHR
  , 
    
    
    SwapchainCreateInfoKHR es -> SurfaceKHR
surface :: SurfaceKHR
  , 
    
    
    SwapchainCreateInfoKHR es -> Word32
minImageCount :: Word32
  , 
    
    SwapchainCreateInfoKHR es -> Format
imageFormat :: Format
  , 
    
    SwapchainCreateInfoKHR es -> ColorSpaceKHR
imageColorSpace :: ColorSpaceKHR
  , 
    
    
    
    
    
    
    
    
    
    SwapchainCreateInfoKHR es -> Extent2D
imageExtent :: Extent2D
  , 
    
    SwapchainCreateInfoKHR es -> Word32
imageArrayLayers :: Word32
  , 
    
    
    SwapchainCreateInfoKHR es -> ImageUsageFlags
imageUsage :: ImageUsageFlags
  , 
    
    SwapchainCreateInfoKHR es -> SharingMode
imageSharingMode :: SharingMode
  , 
    
    
    SwapchainCreateInfoKHR es -> Vector Word32
queueFamilyIndices :: Vector Word32
  , 
    
    
    
    
    
    
    
    SwapchainCreateInfoKHR es -> SurfaceTransformFlagBitsKHR
preTransform :: SurfaceTransformFlagBitsKHR
  , 
    
    
    
    SwapchainCreateInfoKHR es -> CompositeAlphaFlagBitsKHR
compositeAlpha :: CompositeAlphaFlagBitsKHR
  , 
    
    
    SwapchainCreateInfoKHR es -> PresentModeKHR
presentMode :: PresentModeKHR
  , 
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    SwapchainCreateInfoKHR es -> Bool
clipped :: Bool
  , 
    
    
    
    
    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
  extensibleTypeName :: String
extensibleTypeName = String
"SwapchainCreateInfoKHR"
  setNext :: SwapchainCreateInfoKHR ds -> Chain es -> SwapchainCreateInfoKHR es
setNext SwapchainCreateInfoKHR{Bool
Word32
Vector Word32
Chain ds
Format
ImageUsageFlags
Extent2D
SwapchainKHR
SurfaceKHR
PresentModeKHR
SharingMode
SurfaceTransformFlagBitsKHR
CompositeAlphaFlagBitsKHR
ColorSpaceKHR
SwapchainCreateFlagsKHR
oldSwapchain :: SwapchainKHR
clipped :: Bool
presentMode :: PresentModeKHR
compositeAlpha :: CompositeAlphaFlagBitsKHR
preTransform :: SurfaceTransformFlagBitsKHR
queueFamilyIndices :: Vector Word32
imageSharingMode :: SharingMode
imageUsage :: ImageUsageFlags
imageArrayLayers :: Word32
imageExtent :: Extent2D
imageColorSpace :: ColorSpaceKHR
imageFormat :: Format
minImageCount :: Word32
surface :: SurfaceKHR
flags :: SwapchainCreateFlagsKHR
next :: Chain ds
$sel:oldSwapchain:SwapchainCreateInfoKHR :: forall (es :: [*]). SwapchainCreateInfoKHR es -> SwapchainKHR
$sel:clipped:SwapchainCreateInfoKHR :: forall (es :: [*]). SwapchainCreateInfoKHR es -> Bool
$sel:presentMode:SwapchainCreateInfoKHR :: forall (es :: [*]). SwapchainCreateInfoKHR es -> PresentModeKHR
$sel:compositeAlpha:SwapchainCreateInfoKHR :: forall (es :: [*]).
SwapchainCreateInfoKHR es -> CompositeAlphaFlagBitsKHR
$sel:preTransform:SwapchainCreateInfoKHR :: forall (es :: [*]).
SwapchainCreateInfoKHR es -> SurfaceTransformFlagBitsKHR
$sel:queueFamilyIndices:SwapchainCreateInfoKHR :: forall (es :: [*]). SwapchainCreateInfoKHR es -> Vector Word32
$sel:imageSharingMode:SwapchainCreateInfoKHR :: forall (es :: [*]). SwapchainCreateInfoKHR es -> SharingMode
$sel:imageUsage:SwapchainCreateInfoKHR :: forall (es :: [*]). SwapchainCreateInfoKHR es -> ImageUsageFlags
$sel:imageArrayLayers:SwapchainCreateInfoKHR :: forall (es :: [*]). SwapchainCreateInfoKHR es -> Word32
$sel:imageExtent:SwapchainCreateInfoKHR :: forall (es :: [*]). SwapchainCreateInfoKHR es -> Extent2D
$sel:imageColorSpace:SwapchainCreateInfoKHR :: forall (es :: [*]). SwapchainCreateInfoKHR es -> ColorSpaceKHR
$sel:imageFormat:SwapchainCreateInfoKHR :: forall (es :: [*]). SwapchainCreateInfoKHR es -> Format
$sel:minImageCount:SwapchainCreateInfoKHR :: forall (es :: [*]). SwapchainCreateInfoKHR es -> Word32
$sel:surface:SwapchainCreateInfoKHR :: forall (es :: [*]). SwapchainCreateInfoKHR es -> SurfaceKHR
$sel:flags:SwapchainCreateInfoKHR :: forall (es :: [*]).
SwapchainCreateInfoKHR es -> SwapchainCreateFlagsKHR
$sel:next:SwapchainCreateInfoKHR :: forall (es :: [*]). SwapchainCreateInfoKHR es -> Chain es
..} Chain es
next' = SwapchainCreateInfoKHR :: forall (es :: [*]).
Chain es
-> SwapchainCreateFlagsKHR
-> SurfaceKHR
-> Word32
-> Format
-> ColorSpaceKHR
-> Extent2D
-> Word32
-> ImageUsageFlags
-> SharingMode
-> Vector Word32
-> SurfaceTransformFlagBitsKHR
-> CompositeAlphaFlagBitsKHR
-> PresentModeKHR
-> Bool
-> SwapchainKHR
-> SwapchainCreateInfoKHR es
SwapchainCreateInfoKHR{$sel:next:SwapchainCreateInfoKHR :: Chain es
next = Chain es
next', Bool
Word32
Vector Word32
Format
ImageUsageFlags
Extent2D
SwapchainKHR
SurfaceKHR
PresentModeKHR
SharingMode
SurfaceTransformFlagBitsKHR
CompositeAlphaFlagBitsKHR
ColorSpaceKHR
SwapchainCreateFlagsKHR
oldSwapchain :: SwapchainKHR
clipped :: Bool
presentMode :: PresentModeKHR
compositeAlpha :: CompositeAlphaFlagBitsKHR
preTransform :: SurfaceTransformFlagBitsKHR
queueFamilyIndices :: Vector Word32
imageSharingMode :: SharingMode
imageUsage :: ImageUsageFlags
imageArrayLayers :: Word32
imageExtent :: Extent2D
imageColorSpace :: ColorSpaceKHR
imageFormat :: Format
minImageCount :: Word32
surface :: SurfaceKHR
flags :: SwapchainCreateFlagsKHR
$sel:oldSwapchain:SwapchainCreateInfoKHR :: SwapchainKHR
$sel:clipped:SwapchainCreateInfoKHR :: Bool
$sel:presentMode:SwapchainCreateInfoKHR :: PresentModeKHR
$sel:compositeAlpha:SwapchainCreateInfoKHR :: CompositeAlphaFlagBitsKHR
$sel:preTransform:SwapchainCreateInfoKHR :: SurfaceTransformFlagBitsKHR
$sel:queueFamilyIndices:SwapchainCreateInfoKHR :: Vector Word32
$sel:imageSharingMode:SwapchainCreateInfoKHR :: SharingMode
$sel:imageUsage:SwapchainCreateInfoKHR :: ImageUsageFlags
$sel:imageArrayLayers:SwapchainCreateInfoKHR :: Word32
$sel:imageExtent:SwapchainCreateInfoKHR :: Extent2D
$sel:imageColorSpace:SwapchainCreateInfoKHR :: ColorSpaceKHR
$sel:imageFormat:SwapchainCreateInfoKHR :: Format
$sel:minImageCount:SwapchainCreateInfoKHR :: Word32
$sel:surface:SwapchainCreateInfoKHR :: SurfaceKHR
$sel:flags:SwapchainCreateInfoKHR :: SwapchainCreateFlagsKHR
..}
  getNext :: SwapchainCreateInfoKHR es -> Chain es
getNext SwapchainCreateInfoKHR{Bool
Word32
Vector Word32
Chain es
Format
ImageUsageFlags
Extent2D
SwapchainKHR
SurfaceKHR
PresentModeKHR
SharingMode
SurfaceTransformFlagBitsKHR
CompositeAlphaFlagBitsKHR
ColorSpaceKHR
SwapchainCreateFlagsKHR
oldSwapchain :: SwapchainKHR
clipped :: Bool
presentMode :: PresentModeKHR
compositeAlpha :: CompositeAlphaFlagBitsKHR
preTransform :: SurfaceTransformFlagBitsKHR
queueFamilyIndices :: Vector Word32
imageSharingMode :: SharingMode
imageUsage :: ImageUsageFlags
imageArrayLayers :: Word32
imageExtent :: Extent2D
imageColorSpace :: ColorSpaceKHR
imageFormat :: Format
minImageCount :: Word32
surface :: SurfaceKHR
flags :: SwapchainCreateFlagsKHR
next :: Chain es
$sel:oldSwapchain:SwapchainCreateInfoKHR :: forall (es :: [*]). SwapchainCreateInfoKHR es -> SwapchainKHR
$sel:clipped:SwapchainCreateInfoKHR :: forall (es :: [*]). SwapchainCreateInfoKHR es -> Bool
$sel:presentMode:SwapchainCreateInfoKHR :: forall (es :: [*]). SwapchainCreateInfoKHR es -> PresentModeKHR
$sel:compositeAlpha:SwapchainCreateInfoKHR :: forall (es :: [*]).
SwapchainCreateInfoKHR es -> CompositeAlphaFlagBitsKHR
$sel:preTransform:SwapchainCreateInfoKHR :: forall (es :: [*]).
SwapchainCreateInfoKHR es -> SurfaceTransformFlagBitsKHR
$sel:queueFamilyIndices:SwapchainCreateInfoKHR :: forall (es :: [*]). SwapchainCreateInfoKHR es -> Vector Word32
$sel:imageSharingMode:SwapchainCreateInfoKHR :: forall (es :: [*]). SwapchainCreateInfoKHR es -> SharingMode
$sel:imageUsage:SwapchainCreateInfoKHR :: forall (es :: [*]). SwapchainCreateInfoKHR es -> ImageUsageFlags
$sel:imageArrayLayers:SwapchainCreateInfoKHR :: forall (es :: [*]). SwapchainCreateInfoKHR es -> Word32
$sel:imageExtent:SwapchainCreateInfoKHR :: forall (es :: [*]). SwapchainCreateInfoKHR es -> Extent2D
$sel:imageColorSpace:SwapchainCreateInfoKHR :: forall (es :: [*]). SwapchainCreateInfoKHR es -> ColorSpaceKHR
$sel:imageFormat:SwapchainCreateInfoKHR :: forall (es :: [*]). SwapchainCreateInfoKHR es -> Format
$sel:minImageCount:SwapchainCreateInfoKHR :: forall (es :: [*]). SwapchainCreateInfoKHR es -> Word32
$sel:surface:SwapchainCreateInfoKHR :: forall (es :: [*]). SwapchainCreateInfoKHR es -> SurfaceKHR
$sel:flags:SwapchainCreateInfoKHR :: forall (es :: [*]).
SwapchainCreateInfoKHR es -> SwapchainCreateFlagsKHR
$sel:next:SwapchainCreateInfoKHR :: forall (es :: [*]). SwapchainCreateInfoKHR es -> Chain es
..} = 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 proxy e
_ Extends SwapchainCreateInfoKHR e => b
f
    | Just e :~: SurfaceFullScreenExclusiveWin32InfoEXT
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 e :~: SurfaceFullScreenExclusiveInfoEXT
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 e :~: ImageFormatListCreateInfo
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 e :~: SwapchainDisplayNativeHdrCreateInfoAMD
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 e :~: DeviceGroupSwapchainCreateInfoKHR
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 e :~: SwapchainCounterCreateInfoEXT
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 SwapchainCreateInfoKHR es
x Ptr (SwapchainCreateInfoKHR es) -> IO b
f = Int -> (Ptr (SwapchainCreateInfoKHR es) -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
104 ((Ptr (SwapchainCreateInfoKHR es) -> IO b) -> IO b)
-> (Ptr (SwapchainCreateInfoKHR es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \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 Ptr (SwapchainCreateInfoKHR es)
p SwapchainCreateInfoKHR{Bool
Word32
Vector Word32
Chain es
Format
ImageUsageFlags
Extent2D
SwapchainKHR
SurfaceKHR
PresentModeKHR
SharingMode
SurfaceTransformFlagBitsKHR
CompositeAlphaFlagBitsKHR
ColorSpaceKHR
SwapchainCreateFlagsKHR
oldSwapchain :: SwapchainKHR
clipped :: Bool
presentMode :: PresentModeKHR
compositeAlpha :: CompositeAlphaFlagBitsKHR
preTransform :: SurfaceTransformFlagBitsKHR
queueFamilyIndices :: Vector Word32
imageSharingMode :: SharingMode
imageUsage :: ImageUsageFlags
imageArrayLayers :: Word32
imageExtent :: Extent2D
imageColorSpace :: ColorSpaceKHR
imageFormat :: Format
minImageCount :: Word32
surface :: SurfaceKHR
flags :: SwapchainCreateFlagsKHR
next :: Chain es
$sel:oldSwapchain:SwapchainCreateInfoKHR :: forall (es :: [*]). SwapchainCreateInfoKHR es -> SwapchainKHR
$sel:clipped:SwapchainCreateInfoKHR :: forall (es :: [*]). SwapchainCreateInfoKHR es -> Bool
$sel:presentMode:SwapchainCreateInfoKHR :: forall (es :: [*]). SwapchainCreateInfoKHR es -> PresentModeKHR
$sel:compositeAlpha:SwapchainCreateInfoKHR :: forall (es :: [*]).
SwapchainCreateInfoKHR es -> CompositeAlphaFlagBitsKHR
$sel:preTransform:SwapchainCreateInfoKHR :: forall (es :: [*]).
SwapchainCreateInfoKHR es -> SurfaceTransformFlagBitsKHR
$sel:queueFamilyIndices:SwapchainCreateInfoKHR :: forall (es :: [*]). SwapchainCreateInfoKHR es -> Vector Word32
$sel:imageSharingMode:SwapchainCreateInfoKHR :: forall (es :: [*]). SwapchainCreateInfoKHR es -> SharingMode
$sel:imageUsage:SwapchainCreateInfoKHR :: forall (es :: [*]). SwapchainCreateInfoKHR es -> ImageUsageFlags
$sel:imageArrayLayers:SwapchainCreateInfoKHR :: forall (es :: [*]). SwapchainCreateInfoKHR es -> Word32
$sel:imageExtent:SwapchainCreateInfoKHR :: forall (es :: [*]). SwapchainCreateInfoKHR es -> Extent2D
$sel:imageColorSpace:SwapchainCreateInfoKHR :: forall (es :: [*]). SwapchainCreateInfoKHR es -> ColorSpaceKHR
$sel:imageFormat:SwapchainCreateInfoKHR :: forall (es :: [*]). SwapchainCreateInfoKHR es -> Format
$sel:minImageCount:SwapchainCreateInfoKHR :: forall (es :: [*]). SwapchainCreateInfoKHR es -> Word32
$sel:surface:SwapchainCreateInfoKHR :: forall (es :: [*]). SwapchainCreateInfoKHR es -> SurfaceKHR
$sel:flags:SwapchainCreateInfoKHR :: forall (es :: [*]).
SwapchainCreateInfoKHR es -> SwapchainCreateFlagsKHR
$sel:next:SwapchainCreateInfoKHR :: forall (es :: [*]). SwapchainCreateInfoKHR es -> Chain es
..} 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` Int
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` Int
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` Int
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` Int
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` Int
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` Int
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` Int
40 :: Ptr ColorSpaceKHR)) (ColorSpaceKHR
imageColorSpace)
    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 Extent2D -> Extent2D -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es) -> Int -> Ptr Extent2D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
44 :: Ptr Extent2D)) (Extent2D
imageExtent)
    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` Int
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` Int
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` Int
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` Int
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 -> (("pSwapchainImageCount" ::: Ptr Word32) -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes @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
* Int
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_ (\Int
i 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` (Int
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` Int
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` Int
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` Int
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` Int
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` Int
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` Int
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 = Int
104
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: Ptr (SwapchainCreateInfoKHR es) -> IO b -> IO b
pokeZeroCStruct Ptr (SwapchainCreateInfoKHR es)
p 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` Int
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` Int
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` Int
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` Int
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` Int
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` Int
40 :: Ptr ColorSpaceKHR)) (ColorSpaceKHR
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 Extent2D -> Extent2D -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SwapchainCreateInfoKHR es)
p Ptr (SwapchainCreateInfoKHR es) -> Int -> Ptr Extent2D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
44 :: Ptr Extent2D)) (Extent2D
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` Int
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` Int
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` Int
60 :: Ptr SharingMode)) (SharingMode
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 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` Int
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` Int
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` Int
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` Int
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 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` Int
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` Int
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` Int
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` Int
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` Int
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` Int
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` Int
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` Int
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` Int
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` Int
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` Int
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` Int
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) (\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` (Int
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` Int
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` Int
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` Int
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` Int
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` Int
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
data PresentInfoKHR (es :: [Type]) = PresentInfoKHR
  { 
    PresentInfoKHR es -> Chain es
next :: Chain es
  , 
    
    
    
    PresentInfoKHR es -> Vector Semaphore
waitSemaphores :: Vector Semaphore
  , 
    
    
    
    PresentInfoKHR es -> Vector SwapchainKHR
swapchains :: Vector SwapchainKHR
  , 
    
    
    
    PresentInfoKHR es -> Vector Word32
imageIndices :: Vector Word32
  , 
    
    
    
    
    
    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
  extensibleTypeName :: String
extensibleTypeName = String
"PresentInfoKHR"
  setNext :: PresentInfoKHR ds -> Chain es -> PresentInfoKHR es
setNext PresentInfoKHR{Ptr Result
Vector Word32
Vector Semaphore
Vector SwapchainKHR
Chain ds
results :: Ptr Result
imageIndices :: Vector Word32
swapchains :: Vector SwapchainKHR
waitSemaphores :: Vector Semaphore
next :: Chain ds
$sel:results:PresentInfoKHR :: forall (es :: [*]). PresentInfoKHR es -> Ptr Result
$sel:imageIndices:PresentInfoKHR :: forall (es :: [*]). PresentInfoKHR es -> Vector Word32
$sel:swapchains:PresentInfoKHR :: forall (es :: [*]). PresentInfoKHR es -> Vector SwapchainKHR
$sel:waitSemaphores:PresentInfoKHR :: forall (es :: [*]). PresentInfoKHR es -> Vector Semaphore
$sel:next:PresentInfoKHR :: forall (es :: [*]). PresentInfoKHR es -> Chain es
..} Chain es
next' = PresentInfoKHR :: forall (es :: [*]).
Chain es
-> Vector Semaphore
-> Vector SwapchainKHR
-> Vector Word32
-> Ptr Result
-> PresentInfoKHR es
PresentInfoKHR{$sel:next:PresentInfoKHR :: Chain es
next = Chain es
next', Ptr Result
Vector Word32
Vector Semaphore
Vector SwapchainKHR
results :: Ptr Result
imageIndices :: Vector Word32
swapchains :: Vector SwapchainKHR
waitSemaphores :: Vector Semaphore
$sel:results:PresentInfoKHR :: Ptr Result
$sel:imageIndices:PresentInfoKHR :: Vector Word32
$sel:swapchains:PresentInfoKHR :: Vector SwapchainKHR
$sel:waitSemaphores:PresentInfoKHR :: Vector Semaphore
..}
  getNext :: PresentInfoKHR es -> Chain es
getNext PresentInfoKHR{Ptr Result
Vector Word32
Vector Semaphore
Vector SwapchainKHR
Chain es
results :: Ptr Result
imageIndices :: Vector Word32
swapchains :: Vector SwapchainKHR
waitSemaphores :: Vector Semaphore
next :: Chain es
$sel:results:PresentInfoKHR :: forall (es :: [*]). PresentInfoKHR es -> Ptr Result
$sel:imageIndices:PresentInfoKHR :: forall (es :: [*]). PresentInfoKHR es -> Vector Word32
$sel:swapchains:PresentInfoKHR :: forall (es :: [*]). PresentInfoKHR es -> Vector SwapchainKHR
$sel:waitSemaphores:PresentInfoKHR :: forall (es :: [*]). PresentInfoKHR es -> Vector Semaphore
$sel:next:PresentInfoKHR :: forall (es :: [*]). PresentInfoKHR es -> Chain es
..} = 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 proxy e
_ Extends PresentInfoKHR e => b
f
    | Just e :~: PresentFrameTokenGGP
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 e :~: PresentTimesInfoGOOGLE
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 e :~: PresentIdKHR
Refl <- (Typeable e, Typeable PresentIdKHR) => Maybe (e :~: PresentIdKHR)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PresentIdKHR = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PresentInfoKHR e => b
f
    | Just e :~: DeviceGroupPresentInfoKHR
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 e :~: PresentRegionsKHR
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 e :~: DisplayPresentInfoKHR
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 PresentInfoKHR es
x Ptr (PresentInfoKHR es) -> IO b
f = Int -> (Ptr (PresentInfoKHR es) -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
64 ((Ptr (PresentInfoKHR es) -> IO b) -> IO b)
-> (Ptr (PresentInfoKHR es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \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 Ptr (PresentInfoKHR es)
p PresentInfoKHR{Ptr Result
Vector Word32
Vector Semaphore
Vector SwapchainKHR
Chain es
results :: Ptr Result
imageIndices :: Vector Word32
swapchains :: Vector SwapchainKHR
waitSemaphores :: Vector Semaphore
next :: Chain es
$sel:results:PresentInfoKHR :: forall (es :: [*]). PresentInfoKHR es -> Ptr Result
$sel:imageIndices:PresentInfoKHR :: forall (es :: [*]). PresentInfoKHR es -> Vector Word32
$sel:swapchains:PresentInfoKHR :: forall (es :: [*]). PresentInfoKHR es -> Vector SwapchainKHR
$sel:waitSemaphores:PresentInfoKHR :: forall (es :: [*]). PresentInfoKHR es -> Vector Semaphore
$sel:next:PresentInfoKHR :: forall (es :: [*]). PresentInfoKHR es -> Chain es
..} 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` Int
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` Int
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` Int
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 -> (Ptr Semaphore -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes @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
* Int
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_ (\Int
i 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` (Int
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` Int
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 String
"" String
"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` Int
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 -> (("pSwapchain" ::: Ptr SwapchainKHR) -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes @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
* Int
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_ (\Int
i 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` (Int
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` Int
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 -> (("pSwapchainImageCount" ::: Ptr Word32) -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes @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
* Int
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_ (\Int
i 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` (Int
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` Int
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` Int
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 = Int
64
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: Ptr (PresentInfoKHR es) -> IO b -> IO b
pokeZeroCStruct Ptr (PresentInfoKHR es)
p 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` Int
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` Int
8 :: Ptr (Ptr ()))) Ptr ()
pNext'
    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 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` Int
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` Int
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` Int
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) (\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` (Int
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` Int
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` Int
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) (\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` (Int
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` Int
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) (\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` (Int
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` Int
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
data DeviceGroupPresentCapabilitiesKHR = DeviceGroupPresentCapabilitiesKHR
  { 
    
    
    
    
    
    DeviceGroupPresentCapabilitiesKHR -> Vector Word32
presentMask :: Vector Word32
  , 
    
    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 DeviceGroupPresentCapabilitiesKHR
x ("pDeviceGroupPresentCapabilities"
 ::: Ptr DeviceGroupPresentCapabilitiesKHR)
-> IO b
f = Int
-> (("pDeviceGroupPresentCapabilities"
     ::: Ptr DeviceGroupPresentCapabilitiesKHR)
    -> IO b)
-> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
152 ((("pDeviceGroupPresentCapabilities"
   ::: Ptr DeviceGroupPresentCapabilitiesKHR)
  -> IO b)
 -> IO b)
-> (("pDeviceGroupPresentCapabilities"
     ::: Ptr DeviceGroupPresentCapabilitiesKHR)
    -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \"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 "pDeviceGroupPresentCapabilities"
::: Ptr DeviceGroupPresentCapabilitiesKHR
p DeviceGroupPresentCapabilitiesKHR{Vector Word32
"modes" ::: DeviceGroupPresentModeFlagsKHR
modes :: "modes" ::: DeviceGroupPresentModeFlagsKHR
presentMask :: Vector Word32
$sel:modes:DeviceGroupPresentCapabilitiesKHR :: DeviceGroupPresentCapabilitiesKHR
-> "modes" ::: DeviceGroupPresentModeFlagsKHR
$sel:presentMask:DeviceGroupPresentCapabilitiesKHR :: DeviceGroupPresentCapabilitiesKHR -> Vector Word32
..} 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` Int
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` Int
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 String
"" String
"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_ (\Int
i 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` Int
16 :: Ptr (FixedArray MAX_DEVICE_GROUP_SIZE Word32)))) ("pSwapchainImageCount" ::: Ptr Word32)
-> Int -> "pSwapchainImageCount" ::: Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
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` Int
144 :: Ptr DeviceGroupPresentModeFlagsKHR)) ("modes" ::: DeviceGroupPresentModeFlagsKHR
modes)
    IO b
f
  cStructSize :: Int
cStructSize = Int
152
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: ("pDeviceGroupPresentCapabilities"
 ::: Ptr DeviceGroupPresentCapabilitiesKHR)
-> IO b -> IO b
pokeZeroCStruct "pDeviceGroupPresentCapabilities"
::: Ptr DeviceGroupPresentCapabilitiesKHR
p 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` Int
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` Int
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 (("pDeviceGroupPresentCapabilities"
::: Ptr DeviceGroupPresentCapabilitiesKHR
p ("pDeviceGroupPresentCapabilities"
 ::: Ptr DeviceGroupPresentCapabilitiesKHR)
-> Int
-> "pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
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 "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) (\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` Int
16 :: Ptr (FixedArray MAX_DEVICE_GROUP_SIZE Word32)))) ("pSwapchainImageCount" ::: Ptr Word32)
-> Int -> "pSwapchainImageCount" ::: Ptr Word32
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
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` Int
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
_ = Int
152
  alignment :: DeviceGroupPresentCapabilitiesKHR -> Int
alignment ~DeviceGroupPresentCapabilitiesKHR
_ = Int
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 "pDeviceGroupPresentCapabilities"
::: Ptr DeviceGroupPresentCapabilitiesKHR
ptr 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
data ImageSwapchainCreateInfoKHR = ImageSwapchainCreateInfoKHR
  { 
    
    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 ImageSwapchainCreateInfoKHR
x Ptr ImageSwapchainCreateInfoKHR -> IO b
f = Int -> (Ptr ImageSwapchainCreateInfoKHR -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 ((Ptr ImageSwapchainCreateInfoKHR -> IO b) -> IO b)
-> (Ptr ImageSwapchainCreateInfoKHR -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \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 Ptr ImageSwapchainCreateInfoKHR
p ImageSwapchainCreateInfoKHR{SwapchainKHR
swapchain :: SwapchainKHR
$sel:swapchain:ImageSwapchainCreateInfoKHR :: ImageSwapchainCreateInfoKHR -> SwapchainKHR
..} 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` Int
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` Int
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` Int
16 :: Ptr SwapchainKHR)) (SwapchainKHR
swapchain)
    IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: Ptr ImageSwapchainCreateInfoKHR -> IO b -> IO b
pokeZeroCStruct Ptr ImageSwapchainCreateInfoKHR
p 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` Int
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` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    IO b
f
instance FromCStruct ImageSwapchainCreateInfoKHR where
  peekCStruct :: Ptr ImageSwapchainCreateInfoKHR -> IO ImageSwapchainCreateInfoKHR
peekCStruct 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` Int
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
_ = Int
24
  alignment :: ImageSwapchainCreateInfoKHR -> Int
alignment ~ImageSwapchainCreateInfoKHR
_ = Int
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 ImageSwapchainCreateInfoKHR
ptr 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
data BindImageMemorySwapchainInfoKHR = BindImageMemorySwapchainInfoKHR
  { 
    
    BindImageMemorySwapchainInfoKHR -> SwapchainKHR
swapchain :: SwapchainKHR
  , 
    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 BindImageMemorySwapchainInfoKHR
x Ptr BindImageMemorySwapchainInfoKHR -> IO b
f = Int -> (Ptr BindImageMemorySwapchainInfoKHR -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 ((Ptr BindImageMemorySwapchainInfoKHR -> IO b) -> IO b)
-> (Ptr BindImageMemorySwapchainInfoKHR -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \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 Ptr BindImageMemorySwapchainInfoKHR
p BindImageMemorySwapchainInfoKHR{Word32
SwapchainKHR
imageIndex :: Word32
swapchain :: SwapchainKHR
$sel:imageIndex:BindImageMemorySwapchainInfoKHR :: BindImageMemorySwapchainInfoKHR -> Word32
$sel:swapchain:BindImageMemorySwapchainInfoKHR :: BindImageMemorySwapchainInfoKHR -> SwapchainKHR
..} 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` Int
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` Int
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` Int
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` Int
24 :: Ptr Word32)) (Word32
imageIndex)
    IO b
f
  cStructSize :: Int
cStructSize = Int
32
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: Ptr BindImageMemorySwapchainInfoKHR -> IO b -> IO b
pokeZeroCStruct Ptr BindImageMemorySwapchainInfoKHR
p 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` Int
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` Int
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` Int
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` Int
24 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO b
f
instance FromCStruct BindImageMemorySwapchainInfoKHR where
  peekCStruct :: Ptr BindImageMemorySwapchainInfoKHR
-> IO BindImageMemorySwapchainInfoKHR
peekCStruct 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` Int
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` Int
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
_ = Int
32
  alignment :: BindImageMemorySwapchainInfoKHR -> Int
alignment ~BindImageMemorySwapchainInfoKHR
_ = Int
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 BindImageMemorySwapchainInfoKHR
ptr 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
data AcquireNextImageInfoKHR = AcquireNextImageInfoKHR
  { 
    AcquireNextImageInfoKHR -> SwapchainKHR
swapchain :: SwapchainKHR
  , 
    
    AcquireNextImageInfoKHR -> Word64
timeout :: Word64
  , 
    
    AcquireNextImageInfoKHR -> Semaphore
semaphore :: Semaphore
  , 
    
    AcquireNextImageInfoKHR -> Fence
fence :: Fence
  , 
    
    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 AcquireNextImageInfoKHR
x Ptr AcquireNextImageInfoKHR -> IO b
f = Int -> (Ptr AcquireNextImageInfoKHR -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
56 ((Ptr AcquireNextImageInfoKHR -> IO b) -> IO b)
-> (Ptr AcquireNextImageInfoKHR -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \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 Ptr AcquireNextImageInfoKHR
p AcquireNextImageInfoKHR{Word32
Word64
Semaphore
Fence
SwapchainKHR
deviceMask :: Word32
fence :: Fence
semaphore :: Semaphore
timeout :: Word64
swapchain :: SwapchainKHR
$sel:deviceMask:AcquireNextImageInfoKHR :: AcquireNextImageInfoKHR -> Word32
$sel:fence:AcquireNextImageInfoKHR :: AcquireNextImageInfoKHR -> Fence
$sel:semaphore:AcquireNextImageInfoKHR :: AcquireNextImageInfoKHR -> Semaphore
$sel:timeout:AcquireNextImageInfoKHR :: AcquireNextImageInfoKHR -> Word64
$sel:swapchain:AcquireNextImageInfoKHR :: AcquireNextImageInfoKHR -> SwapchainKHR
..} 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` Int
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` Int
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` Int
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` Int
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` Int
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` Int
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` Int
48 :: Ptr Word32)) (Word32
deviceMask)
    IO b
f
  cStructSize :: Int
cStructSize = Int
56
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: Ptr AcquireNextImageInfoKHR -> IO b -> IO b
pokeZeroCStruct Ptr AcquireNextImageInfoKHR
p 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` Int
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` Int
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` Int
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` Int
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` Int
48 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO b
f
instance FromCStruct AcquireNextImageInfoKHR where
  peekCStruct :: Ptr AcquireNextImageInfoKHR -> IO AcquireNextImageInfoKHR
peekCStruct 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` Int
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` Int
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` Int
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` Int
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` Int
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
_ = Int
56
  alignment :: AcquireNextImageInfoKHR -> Int
alignment ~AcquireNextImageInfoKHR
_ = Int
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 AcquireNextImageInfoKHR
ptr 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
data DeviceGroupPresentInfoKHR = DeviceGroupPresentInfoKHR
  { 
    
    DeviceGroupPresentInfoKHR -> Vector Word32
deviceMasks :: Vector Word32
  , 
    
    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 DeviceGroupPresentInfoKHR
x Ptr DeviceGroupPresentInfoKHR -> IO b
f = Int -> (Ptr DeviceGroupPresentInfoKHR -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
40 ((Ptr DeviceGroupPresentInfoKHR -> IO b) -> IO b)
-> (Ptr DeviceGroupPresentInfoKHR -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \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 Ptr DeviceGroupPresentInfoKHR
p DeviceGroupPresentInfoKHR{Vector Word32
"modes" ::: DeviceGroupPresentModeFlagsKHR
mode :: "modes" ::: DeviceGroupPresentModeFlagsKHR
deviceMasks :: Vector Word32
$sel:mode:DeviceGroupPresentInfoKHR :: DeviceGroupPresentInfoKHR
-> "modes" ::: DeviceGroupPresentModeFlagsKHR
$sel:deviceMasks:DeviceGroupPresentInfoKHR :: DeviceGroupPresentInfoKHR -> Vector Word32
..} 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` Int
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` Int
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` Int
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 -> (("pSwapchainImageCount" ::: Ptr Word32) -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes @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
* Int
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_ (\Int
i 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` (Int
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` Int
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` Int
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 = Int
40
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: Ptr DeviceGroupPresentInfoKHR -> IO b -> IO b
pokeZeroCStruct Ptr DeviceGroupPresentInfoKHR
p IO b
f = do
    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` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEVICE_GROUP_PRESENT_INFO_KHR)
    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` Int
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 DeviceGroupPresentInfoKHR
p Ptr DeviceGroupPresentInfoKHR
-> Int
-> "pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr DeviceGroupPresentModeFlagBitsKHR)) ("modes" ::: DeviceGroupPresentModeFlagsKHR
forall a. Zero a => a
zero)
    IO b
f
instance FromCStruct DeviceGroupPresentInfoKHR where
  peekCStruct :: Ptr DeviceGroupPresentInfoKHR -> IO DeviceGroupPresentInfoKHR
peekCStruct 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` Int
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` Int
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) (\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` (Int
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` Int
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
data DeviceGroupSwapchainCreateInfoKHR = DeviceGroupSwapchainCreateInfoKHR
  { 
    
    
    
    
    
    
    
    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 DeviceGroupSwapchainCreateInfoKHR
x Ptr DeviceGroupSwapchainCreateInfoKHR -> IO b
f = Int -> (Ptr DeviceGroupSwapchainCreateInfoKHR -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 ((Ptr DeviceGroupSwapchainCreateInfoKHR -> IO b) -> IO b)
-> (Ptr DeviceGroupSwapchainCreateInfoKHR -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \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 Ptr DeviceGroupSwapchainCreateInfoKHR
p DeviceGroupSwapchainCreateInfoKHR{"modes" ::: DeviceGroupPresentModeFlagsKHR
modes :: "modes" ::: DeviceGroupPresentModeFlagsKHR
$sel:modes:DeviceGroupSwapchainCreateInfoKHR :: DeviceGroupSwapchainCreateInfoKHR
-> "modes" ::: DeviceGroupPresentModeFlagsKHR
..} 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` Int
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` Int
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` Int
16 :: Ptr DeviceGroupPresentModeFlagsKHR)) ("modes" ::: DeviceGroupPresentModeFlagsKHR
modes)
    IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: Ptr DeviceGroupSwapchainCreateInfoKHR -> IO b -> IO b
pokeZeroCStruct Ptr DeviceGroupSwapchainCreateInfoKHR
p 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` Int
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` Int
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` Int
16 :: Ptr DeviceGroupPresentModeFlagsKHR)) ("modes" ::: DeviceGroupPresentModeFlagsKHR
forall a. Zero a => a
zero)
    IO b
f
instance FromCStruct DeviceGroupSwapchainCreateInfoKHR where
  peekCStruct :: Ptr DeviceGroupSwapchainCreateInfoKHR
-> IO DeviceGroupSwapchainCreateInfoKHR
peekCStruct 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` Int
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
_ = Int
24
  alignment :: DeviceGroupSwapchainCreateInfoKHR -> Int
alignment ~DeviceGroupSwapchainCreateInfoKHR
_ = Int
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 DeviceGroupSwapchainCreateInfoKHR
ptr 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
type DeviceGroupPresentModeFlagsKHR = DeviceGroupPresentModeFlagBitsKHR
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, Bits ("modes" ::: DeviceGroupPresentModeFlagsKHR)
Bits ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> (("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Int)
-> (("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Int)
-> (("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Int)
-> FiniteBits ("modes" ::: DeviceGroupPresentModeFlagsKHR)
("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Int
forall b.
Bits b -> (b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
countTrailingZeros :: ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Int
$ccountTrailingZeros :: ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Int
countLeadingZeros :: ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Int
$ccountLeadingZeros :: ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Int
finiteBitSize :: ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Int
$cfiniteBitSize :: ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Int
$cp1FiniteBits :: Bits ("modes" ::: DeviceGroupPresentModeFlagsKHR)
FiniteBits)
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
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
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
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
conNameDeviceGroupPresentModeFlagBitsKHR :: String
conNameDeviceGroupPresentModeFlagBitsKHR :: String
conNameDeviceGroupPresentModeFlagBitsKHR = String
"DeviceGroupPresentModeFlagBitsKHR"
enumPrefixDeviceGroupPresentModeFlagBitsKHR :: String
enumPrefixDeviceGroupPresentModeFlagBitsKHR :: String
enumPrefixDeviceGroupPresentModeFlagBitsKHR = String
"DEVICE_GROUP_PRESENT_MODE_"
showTableDeviceGroupPresentModeFlagBitsKHR :: [(DeviceGroupPresentModeFlagBitsKHR, String)]
showTableDeviceGroupPresentModeFlagBitsKHR :: [("modes" ::: DeviceGroupPresentModeFlagsKHR, String)]
showTableDeviceGroupPresentModeFlagBitsKHR =
  [ ("modes" ::: DeviceGroupPresentModeFlagsKHR
DEVICE_GROUP_PRESENT_MODE_LOCAL_BIT_KHR             , String
"LOCAL_BIT_KHR")
  , ("modes" ::: DeviceGroupPresentModeFlagsKHR
DEVICE_GROUP_PRESENT_MODE_REMOTE_BIT_KHR            , String
"REMOTE_BIT_KHR")
  , ("modes" ::: DeviceGroupPresentModeFlagsKHR
DEVICE_GROUP_PRESENT_MODE_SUM_BIT_KHR               , String
"SUM_BIT_KHR")
  , ("modes" ::: DeviceGroupPresentModeFlagsKHR
DEVICE_GROUP_PRESENT_MODE_LOCAL_MULTI_DEVICE_BIT_KHR, String
"LOCAL_MULTI_DEVICE_BIT_KHR")
  ]
instance Show DeviceGroupPresentModeFlagBitsKHR where
  showsPrec :: Int -> ("modes" ::: DeviceGroupPresentModeFlagsKHR) -> ShowS
showsPrec = String
-> [("modes" ::: DeviceGroupPresentModeFlagsKHR, String)]
-> String
-> (("modes" ::: DeviceGroupPresentModeFlagsKHR) -> Word32)
-> (Word32 -> ShowS)
-> Int
-> ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ShowS
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec String
enumPrefixDeviceGroupPresentModeFlagBitsKHR
                            [("modes" ::: DeviceGroupPresentModeFlagsKHR, String)]
showTableDeviceGroupPresentModeFlagBitsKHR
                            String
conNameDeviceGroupPresentModeFlagBitsKHR
                            (\(DeviceGroupPresentModeFlagBitsKHR Word32
x) -> Word32
x)
                            (\Word32
x -> String -> ShowS
showString String
"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 = String
-> [("modes" ::: DeviceGroupPresentModeFlagsKHR, String)]
-> String
-> (Word32 -> "modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ReadPrec ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec String
enumPrefixDeviceGroupPresentModeFlagBitsKHR
                          [("modes" ::: DeviceGroupPresentModeFlagsKHR, String)]
showTableDeviceGroupPresentModeFlagBitsKHR
                          String
conNameDeviceGroupPresentModeFlagBitsKHR
                          Word32 -> "modes" ::: DeviceGroupPresentModeFlagsKHR
DeviceGroupPresentModeFlagBitsKHR
type SwapchainCreateFlagsKHR = SwapchainCreateFlagBitsKHR
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, Bits SwapchainCreateFlagsKHR
Bits SwapchainCreateFlagsKHR
-> (SwapchainCreateFlagsKHR -> Int)
-> (SwapchainCreateFlagsKHR -> Int)
-> (SwapchainCreateFlagsKHR -> Int)
-> FiniteBits SwapchainCreateFlagsKHR
SwapchainCreateFlagsKHR -> Int
forall b.
Bits b -> (b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
countTrailingZeros :: SwapchainCreateFlagsKHR -> Int
$ccountTrailingZeros :: SwapchainCreateFlagsKHR -> Int
countLeadingZeros :: SwapchainCreateFlagsKHR -> Int
$ccountLeadingZeros :: SwapchainCreateFlagsKHR -> Int
finiteBitSize :: SwapchainCreateFlagsKHR -> Int
$cfiniteBitSize :: SwapchainCreateFlagsKHR -> Int
$cp1FiniteBits :: Bits SwapchainCreateFlagsKHR
FiniteBits)
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
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
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
conNameSwapchainCreateFlagBitsKHR :: String
conNameSwapchainCreateFlagBitsKHR :: String
conNameSwapchainCreateFlagBitsKHR = String
"SwapchainCreateFlagBitsKHR"
enumPrefixSwapchainCreateFlagBitsKHR :: String
enumPrefixSwapchainCreateFlagBitsKHR :: String
enumPrefixSwapchainCreateFlagBitsKHR = String
"SWAPCHAIN_CREATE_"
showTableSwapchainCreateFlagBitsKHR :: [(SwapchainCreateFlagBitsKHR, String)]
showTableSwapchainCreateFlagBitsKHR :: [(SwapchainCreateFlagsKHR, String)]
showTableSwapchainCreateFlagBitsKHR =
  [ (SwapchainCreateFlagsKHR
SWAPCHAIN_CREATE_MUTABLE_FORMAT_BIT_KHR             , String
"MUTABLE_FORMAT_BIT_KHR")
  , (SwapchainCreateFlagsKHR
SWAPCHAIN_CREATE_SPLIT_INSTANCE_BIND_REGIONS_BIT_KHR, String
"SPLIT_INSTANCE_BIND_REGIONS_BIT_KHR")
  , (SwapchainCreateFlagsKHR
SWAPCHAIN_CREATE_PROTECTED_BIT_KHR                  , String
"PROTECTED_BIT_KHR")
  ]
instance Show SwapchainCreateFlagBitsKHR where
  showsPrec :: Int -> SwapchainCreateFlagsKHR -> ShowS
showsPrec = String
-> [(SwapchainCreateFlagsKHR, String)]
-> String
-> (SwapchainCreateFlagsKHR -> Word32)
-> (Word32 -> ShowS)
-> Int
-> SwapchainCreateFlagsKHR
-> ShowS
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec String
enumPrefixSwapchainCreateFlagBitsKHR
                            [(SwapchainCreateFlagsKHR, String)]
showTableSwapchainCreateFlagBitsKHR
                            String
conNameSwapchainCreateFlagBitsKHR
                            (\(SwapchainCreateFlagBitsKHR Word32
x) -> Word32
x)
                            (\Word32
x -> String -> ShowS
showString String
"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 = String
-> [(SwapchainCreateFlagsKHR, String)]
-> String
-> (Word32 -> SwapchainCreateFlagsKHR)
-> ReadPrec SwapchainCreateFlagsKHR
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec String
enumPrefixSwapchainCreateFlagBitsKHR
                          [(SwapchainCreateFlagsKHR, String)]
showTableSwapchainCreateFlagBitsKHR
                          String
conNameSwapchainCreateFlagBitsKHR
                          Word32 -> SwapchainCreateFlagsKHR
SwapchainCreateFlagBitsKHR
type KHR_SWAPCHAIN_SPEC_VERSION = 70
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"
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"