{-# language CPP #-}
module Vulkan.Extensions.VK_EXT_swapchain_maintenance1  ( releaseSwapchainImagesEXT
                                                        , PhysicalDeviceSwapchainMaintenance1FeaturesEXT(..)
                                                        , SwapchainPresentFenceInfoEXT(..)
                                                        , SwapchainPresentModesCreateInfoEXT(..)
                                                        , SwapchainPresentModeInfoEXT(..)
                                                        , SwapchainPresentScalingCreateInfoEXT(..)
                                                        , ReleaseSwapchainImagesInfoEXT(..)
                                                        , EXT_SWAPCHAIN_MAINTENANCE_1_SPEC_VERSION
                                                        , pattern EXT_SWAPCHAIN_MAINTENANCE_1_SPEC_VERSION
                                                        , EXT_SWAPCHAIN_MAINTENANCE_1_EXTENSION_NAME
                                                        , pattern EXT_SWAPCHAIN_MAINTENANCE_1_EXTENSION_NAME
                                                        , SwapchainKHR(..)
                                                        , PresentModeKHR(..)
                                                        , SwapchainCreateFlagBitsKHR(..)
                                                        , SwapchainCreateFlagsKHR
                                                        , PresentScalingFlagBitsEXT(..)
                                                        , PresentScalingFlagsEXT
                                                        , PresentGravityFlagBitsEXT(..)
                                                        , PresentGravityFlagsEXT
                                                        ) where
import Vulkan.Internal.Utils (traceAroundEvent)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Foreign.Marshal.Alloc (allocaBytes)
import GHC.Base (when)
import GHC.IO (throwIO)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
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 Control.Monad.IO.Class (MonadIO)
import Data.String (IsString)
import Data.Typeable (Typeable)
import Foreign.Storable (Storable)
import Foreign.Storable (Storable(peek))
import Foreign.Storable (Storable(poke))
import qualified Foreign.Storable (Storable(..))
import GHC.Generics (Generic)
import GHC.IO.Exception (IOErrorType(..))
import GHC.IO.Exception (IOException(..))
import Foreign.Ptr (FunPtr)
import Foreign.Ptr (Ptr)
import Data.Word (Word32)
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.NamedType ((:::))
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Core10.Handles (Device(Device))
import Vulkan.Dynamic (DeviceCmds(pVkReleaseSwapchainImagesEXT))
import Vulkan.Core10.Handles (Device_T)
import Vulkan.Core10.Handles (Fence)
import Vulkan.Extensions.VK_EXT_surface_maintenance1 (PresentGravityFlagsEXT)
import Vulkan.Extensions.VK_KHR_surface (PresentModeKHR)
import Vulkan.Extensions.VK_EXT_surface_maintenance1 (PresentScalingFlagsEXT)
import Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Extensions.Handles (SwapchainKHR)
import Vulkan.Exception (VulkanException(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_SWAPCHAIN_MAINTENANCE_1_FEATURES_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_RELEASE_SWAPCHAIN_IMAGES_INFO_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_SWAPCHAIN_PRESENT_FENCE_INFO_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_SWAPCHAIN_PRESENT_MODES_CREATE_INFO_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_SWAPCHAIN_PRESENT_MODE_INFO_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_SWAPCHAIN_PRESENT_SCALING_CREATE_INFO_EXT))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
import Vulkan.Extensions.VK_EXT_surface_maintenance1 (PresentGravityFlagBitsEXT(..))
import Vulkan.Extensions.VK_EXT_surface_maintenance1 (PresentGravityFlagsEXT)
import Vulkan.Extensions.VK_KHR_surface (PresentModeKHR(..))
import Vulkan.Extensions.VK_EXT_surface_maintenance1 (PresentScalingFlagBitsEXT(..))
import Vulkan.Extensions.VK_EXT_surface_maintenance1 (PresentScalingFlagsEXT)
import Vulkan.Extensions.VK_KHR_swapchain (SwapchainCreateFlagBitsKHR(..))
import Vulkan.Extensions.VK_KHR_swapchain (SwapchainCreateFlagsKHR)
import Vulkan.Extensions.Handles (SwapchainKHR(..))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkReleaseSwapchainImagesEXT
  :: FunPtr (Ptr Device_T -> Ptr ReleaseSwapchainImagesInfoEXT -> IO Result) -> Ptr Device_T -> Ptr ReleaseSwapchainImagesInfoEXT -> IO Result
releaseSwapchainImagesEXT :: forall io
                           . (MonadIO io)
                          => 
                             
                             
                             
                             
                             Device
                          -> 
                             
                             
                             
                             
                             
                             ("releaseInfo" ::: ReleaseSwapchainImagesInfoEXT)
                          -> io ()
releaseSwapchainImagesEXT :: forall (io :: * -> *).
MonadIO io =>
Device -> ReleaseSwapchainImagesInfoEXT -> io ()
releaseSwapchainImagesEXT Device
device ReleaseSwapchainImagesInfoEXT
releaseInfo = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
  let vkReleaseSwapchainImagesEXTPtr :: FunPtr
  (Ptr Device_T
   -> ("pReleaseInfo" ::: Ptr ReleaseSwapchainImagesInfoEXT)
   -> IO Result)
vkReleaseSwapchainImagesEXTPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> ("pReleaseInfo" ::: Ptr ReleaseSwapchainImagesInfoEXT)
      -> IO Result)
pVkReleaseSwapchainImagesEXT (case Device
device of Device{DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds :: DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> ("pReleaseInfo" ::: Ptr ReleaseSwapchainImagesInfoEXT)
   -> IO Result)
vkReleaseSwapchainImagesEXTPtr forall a. Eq a => a -> a -> Bool
/= forall a. FunPtr a
nullFunPtr) forall a b. (a -> b) -> a -> b
$
    forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkReleaseSwapchainImagesEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkReleaseSwapchainImagesEXT' :: Ptr Device_T
-> ("pReleaseInfo" ::: Ptr ReleaseSwapchainImagesInfoEXT)
-> IO Result
vkReleaseSwapchainImagesEXT' = FunPtr
  (Ptr Device_T
   -> ("pReleaseInfo" ::: Ptr ReleaseSwapchainImagesInfoEXT)
   -> IO Result)
-> Ptr Device_T
-> ("pReleaseInfo" ::: Ptr ReleaseSwapchainImagesInfoEXT)
-> IO Result
mkVkReleaseSwapchainImagesEXT FunPtr
  (Ptr Device_T
   -> ("pReleaseInfo" ::: Ptr ReleaseSwapchainImagesInfoEXT)
   -> IO Result)
vkReleaseSwapchainImagesEXTPtr
  "pReleaseInfo" ::: Ptr ReleaseSwapchainImagesInfoEXT
pReleaseInfo <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (ReleaseSwapchainImagesInfoEXT
releaseInfo)
  Result
r <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. String -> IO a -> IO a
traceAroundEvent String
"vkReleaseSwapchainImagesEXT" (Ptr Device_T
-> ("pReleaseInfo" ::: Ptr ReleaseSwapchainImagesInfoEXT)
-> IO Result
vkReleaseSwapchainImagesEXT'
                                                                (Device -> Ptr Device_T
deviceHandle (Device
device))
                                                                "pReleaseInfo" ::: Ptr ReleaseSwapchainImagesInfoEXT
pReleaseInfo)
  forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
data PhysicalDeviceSwapchainMaintenance1FeaturesEXT = PhysicalDeviceSwapchainMaintenance1FeaturesEXT
  { 
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    PhysicalDeviceSwapchainMaintenance1FeaturesEXT -> Bool
swapchainMaintenance1 :: Bool }
  deriving (Typeable, PhysicalDeviceSwapchainMaintenance1FeaturesEXT
-> PhysicalDeviceSwapchainMaintenance1FeaturesEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceSwapchainMaintenance1FeaturesEXT
-> PhysicalDeviceSwapchainMaintenance1FeaturesEXT -> Bool
$c/= :: PhysicalDeviceSwapchainMaintenance1FeaturesEXT
-> PhysicalDeviceSwapchainMaintenance1FeaturesEXT -> Bool
== :: PhysicalDeviceSwapchainMaintenance1FeaturesEXT
-> PhysicalDeviceSwapchainMaintenance1FeaturesEXT -> Bool
$c== :: PhysicalDeviceSwapchainMaintenance1FeaturesEXT
-> PhysicalDeviceSwapchainMaintenance1FeaturesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceSwapchainMaintenance1FeaturesEXT)
#endif
deriving instance Show PhysicalDeviceSwapchainMaintenance1FeaturesEXT
instance ToCStruct PhysicalDeviceSwapchainMaintenance1FeaturesEXT where
  withCStruct :: forall b.
PhysicalDeviceSwapchainMaintenance1FeaturesEXT
-> (Ptr PhysicalDeviceSwapchainMaintenance1FeaturesEXT -> IO b)
-> IO b
withCStruct PhysicalDeviceSwapchainMaintenance1FeaturesEXT
x Ptr PhysicalDeviceSwapchainMaintenance1FeaturesEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceSwapchainMaintenance1FeaturesEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceSwapchainMaintenance1FeaturesEXT
p PhysicalDeviceSwapchainMaintenance1FeaturesEXT
x (Ptr PhysicalDeviceSwapchainMaintenance1FeaturesEXT -> IO b
f Ptr PhysicalDeviceSwapchainMaintenance1FeaturesEXT
p)
  pokeCStruct :: forall b.
Ptr PhysicalDeviceSwapchainMaintenance1FeaturesEXT
-> PhysicalDeviceSwapchainMaintenance1FeaturesEXT -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceSwapchainMaintenance1FeaturesEXT
p PhysicalDeviceSwapchainMaintenance1FeaturesEXT{Bool
swapchainMaintenance1 :: Bool
$sel:swapchainMaintenance1:PhysicalDeviceSwapchainMaintenance1FeaturesEXT :: PhysicalDeviceSwapchainMaintenance1FeaturesEXT -> Bool
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSwapchainMaintenance1FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_SWAPCHAIN_MAINTENANCE_1_FEATURES_EXT)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSwapchainMaintenance1FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSwapchainMaintenance1FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
swapchainMaintenance1))
    IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceSwapchainMaintenance1FeaturesEXT -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceSwapchainMaintenance1FeaturesEXT
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSwapchainMaintenance1FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_SWAPCHAIN_MAINTENANCE_1_FEATURES_EXT)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSwapchainMaintenance1FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceSwapchainMaintenance1FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
    IO b
f
instance FromCStruct PhysicalDeviceSwapchainMaintenance1FeaturesEXT where
  peekCStruct :: Ptr PhysicalDeviceSwapchainMaintenance1FeaturesEXT
-> IO PhysicalDeviceSwapchainMaintenance1FeaturesEXT
peekCStruct Ptr PhysicalDeviceSwapchainMaintenance1FeaturesEXT
p = do
    Bool32
swapchainMaintenance1 <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceSwapchainMaintenance1FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Bool -> PhysicalDeviceSwapchainMaintenance1FeaturesEXT
PhysicalDeviceSwapchainMaintenance1FeaturesEXT
             (Bool32 -> Bool
bool32ToBool Bool32
swapchainMaintenance1)
instance Storable PhysicalDeviceSwapchainMaintenance1FeaturesEXT where
  sizeOf :: PhysicalDeviceSwapchainMaintenance1FeaturesEXT -> Int
sizeOf ~PhysicalDeviceSwapchainMaintenance1FeaturesEXT
_ = Int
24
  alignment :: PhysicalDeviceSwapchainMaintenance1FeaturesEXT -> Int
alignment ~PhysicalDeviceSwapchainMaintenance1FeaturesEXT
_ = Int
8
  peek :: Ptr PhysicalDeviceSwapchainMaintenance1FeaturesEXT
-> IO PhysicalDeviceSwapchainMaintenance1FeaturesEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr PhysicalDeviceSwapchainMaintenance1FeaturesEXT
-> PhysicalDeviceSwapchainMaintenance1FeaturesEXT -> IO ()
poke Ptr PhysicalDeviceSwapchainMaintenance1FeaturesEXT
ptr PhysicalDeviceSwapchainMaintenance1FeaturesEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceSwapchainMaintenance1FeaturesEXT
ptr PhysicalDeviceSwapchainMaintenance1FeaturesEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceSwapchainMaintenance1FeaturesEXT where
  zero :: PhysicalDeviceSwapchainMaintenance1FeaturesEXT
zero = Bool -> PhysicalDeviceSwapchainMaintenance1FeaturesEXT
PhysicalDeviceSwapchainMaintenance1FeaturesEXT
           forall a. Zero a => a
zero
data SwapchainPresentFenceInfoEXT = SwapchainPresentFenceInfoEXT
  { 
    
    
    
    SwapchainPresentFenceInfoEXT -> Vector Fence
fences :: Vector Fence }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (SwapchainPresentFenceInfoEXT)
#endif
deriving instance Show SwapchainPresentFenceInfoEXT
instance ToCStruct SwapchainPresentFenceInfoEXT where
  withCStruct :: forall b.
SwapchainPresentFenceInfoEXT
-> (Ptr SwapchainPresentFenceInfoEXT -> IO b) -> IO b
withCStruct SwapchainPresentFenceInfoEXT
x Ptr SwapchainPresentFenceInfoEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 forall a b. (a -> b) -> a -> b
$ \Ptr SwapchainPresentFenceInfoEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr SwapchainPresentFenceInfoEXT
p SwapchainPresentFenceInfoEXT
x (Ptr SwapchainPresentFenceInfoEXT -> IO b
f Ptr SwapchainPresentFenceInfoEXT
p)
  pokeCStruct :: forall b.
Ptr SwapchainPresentFenceInfoEXT
-> SwapchainPresentFenceInfoEXT -> IO b -> IO b
pokeCStruct Ptr SwapchainPresentFenceInfoEXT
p SwapchainPresentFenceInfoEXT{Vector Fence
fences :: Vector Fence
$sel:fences:SwapchainPresentFenceInfoEXT :: SwapchainPresentFenceInfoEXT -> Vector Fence
..} IO b
f = forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SwapchainPresentFenceInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SWAPCHAIN_PRESENT_FENCE_INFO_EXT)
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SwapchainPresentFenceInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SwapchainPresentFenceInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) ((forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Vector a -> Int
Data.Vector.length forall a b. (a -> b) -> a -> b
$ (Vector Fence
fences)) :: Word32))
    Ptr Fence
pPFences' <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes @Fence ((forall a. Vector a -> Int
Data.Vector.length (Vector Fence
fences)) forall a. Num a => a -> a -> a
* Int
8)
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\Int
i Fence
e -> forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Fence
pPFences' forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
8 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Fence) (Fence
e)) (Vector Fence
fences)
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SwapchainPresentFenceInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (Ptr Fence))) (Ptr Fence
pPFences')
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = Int
32
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b. Ptr SwapchainPresentFenceInfoEXT -> IO b -> IO b
pokeZeroCStruct Ptr SwapchainPresentFenceInfoEXT
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SwapchainPresentFenceInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SWAPCHAIN_PRESENT_FENCE_INFO_EXT)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SwapchainPresentFenceInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    IO b
f
instance FromCStruct SwapchainPresentFenceInfoEXT where
  peekCStruct :: Ptr SwapchainPresentFenceInfoEXT -> IO SwapchainPresentFenceInfoEXT
peekCStruct Ptr SwapchainPresentFenceInfoEXT
p = do
    Word32
swapchainCount <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr SwapchainPresentFenceInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32))
    Ptr Fence
pFences <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr Fence) ((Ptr SwapchainPresentFenceInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (Ptr Fence)))
    Vector Fence
pFences' <- forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
swapchainCount) (\Int
i -> forall a. Storable a => Ptr a -> IO a
peek @Fence ((Ptr Fence
pFences forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
8 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Fence)))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Vector Fence -> SwapchainPresentFenceInfoEXT
SwapchainPresentFenceInfoEXT
             Vector Fence
pFences'
instance Zero SwapchainPresentFenceInfoEXT where
  zero :: SwapchainPresentFenceInfoEXT
zero = Vector Fence -> SwapchainPresentFenceInfoEXT
SwapchainPresentFenceInfoEXT
           forall a. Monoid a => a
mempty
data SwapchainPresentModesCreateInfoEXT = SwapchainPresentModesCreateInfoEXT
  { 
    
    SwapchainPresentModesCreateInfoEXT -> Vector PresentModeKHR
presentModes :: Vector PresentModeKHR }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (SwapchainPresentModesCreateInfoEXT)
#endif
deriving instance Show SwapchainPresentModesCreateInfoEXT
instance ToCStruct SwapchainPresentModesCreateInfoEXT where
  withCStruct :: forall b.
SwapchainPresentModesCreateInfoEXT
-> (Ptr SwapchainPresentModesCreateInfoEXT -> IO b) -> IO b
withCStruct SwapchainPresentModesCreateInfoEXT
x Ptr SwapchainPresentModesCreateInfoEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 forall a b. (a -> b) -> a -> b
$ \Ptr SwapchainPresentModesCreateInfoEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr SwapchainPresentModesCreateInfoEXT
p SwapchainPresentModesCreateInfoEXT
x (Ptr SwapchainPresentModesCreateInfoEXT -> IO b
f Ptr SwapchainPresentModesCreateInfoEXT
p)
  pokeCStruct :: forall b.
Ptr SwapchainPresentModesCreateInfoEXT
-> SwapchainPresentModesCreateInfoEXT -> IO b -> IO b
pokeCStruct Ptr SwapchainPresentModesCreateInfoEXT
p SwapchainPresentModesCreateInfoEXT{Vector PresentModeKHR
presentModes :: Vector PresentModeKHR
$sel:presentModes:SwapchainPresentModesCreateInfoEXT :: SwapchainPresentModesCreateInfoEXT -> Vector PresentModeKHR
..} IO b
f = forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SwapchainPresentModesCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SWAPCHAIN_PRESENT_MODES_CREATE_INFO_EXT)
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SwapchainPresentModesCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SwapchainPresentModesCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) ((forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Vector a -> Int
Data.Vector.length forall a b. (a -> b) -> a -> b
$ (Vector PresentModeKHR
presentModes)) :: Word32))
    Ptr PresentModeKHR
pPPresentModes' <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes @PresentModeKHR ((forall a. Vector a -> Int
Data.Vector.length (Vector PresentModeKHR
presentModes)) forall a. Num a => a -> a -> a
* Int
4)
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\Int
i PresentModeKHR
e -> forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr PresentModeKHR
pPPresentModes' forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
4 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr PresentModeKHR) (PresentModeKHR
e)) (Vector PresentModeKHR
presentModes)
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SwapchainPresentModesCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (Ptr PresentModeKHR))) (Ptr PresentModeKHR
pPPresentModes')
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = Int
32
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b. Ptr SwapchainPresentModesCreateInfoEXT -> IO b -> IO b
pokeZeroCStruct Ptr SwapchainPresentModesCreateInfoEXT
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SwapchainPresentModesCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SWAPCHAIN_PRESENT_MODES_CREATE_INFO_EXT)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SwapchainPresentModesCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    IO b
f
instance FromCStruct SwapchainPresentModesCreateInfoEXT where
  peekCStruct :: Ptr SwapchainPresentModesCreateInfoEXT
-> IO SwapchainPresentModesCreateInfoEXT
peekCStruct Ptr SwapchainPresentModesCreateInfoEXT
p = do
    Word32
presentModeCount <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr SwapchainPresentModesCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32))
    Ptr PresentModeKHR
pPresentModes <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr PresentModeKHR) ((Ptr SwapchainPresentModesCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (Ptr PresentModeKHR)))
    Vector PresentModeKHR
pPresentModes' <- forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
presentModeCount) (\Int
i -> forall a. Storable a => Ptr a -> IO a
peek @PresentModeKHR ((Ptr PresentModeKHR
pPresentModes forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
4 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr PresentModeKHR)))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Vector PresentModeKHR -> SwapchainPresentModesCreateInfoEXT
SwapchainPresentModesCreateInfoEXT
             Vector PresentModeKHR
pPresentModes'
instance Zero SwapchainPresentModesCreateInfoEXT where
  zero :: SwapchainPresentModesCreateInfoEXT
zero = Vector PresentModeKHR -> SwapchainPresentModesCreateInfoEXT
SwapchainPresentModesCreateInfoEXT
           forall a. Monoid a => a
mempty
data SwapchainPresentModeInfoEXT = SwapchainPresentModeInfoEXT
  { 
    
    SwapchainPresentModeInfoEXT -> Vector PresentModeKHR
presentModes :: Vector PresentModeKHR }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (SwapchainPresentModeInfoEXT)
#endif
deriving instance Show SwapchainPresentModeInfoEXT
instance ToCStruct SwapchainPresentModeInfoEXT where
  withCStruct :: forall b.
SwapchainPresentModeInfoEXT
-> (Ptr SwapchainPresentModeInfoEXT -> IO b) -> IO b
withCStruct SwapchainPresentModeInfoEXT
x Ptr SwapchainPresentModeInfoEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 forall a b. (a -> b) -> a -> b
$ \Ptr SwapchainPresentModeInfoEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr SwapchainPresentModeInfoEXT
p SwapchainPresentModeInfoEXT
x (Ptr SwapchainPresentModeInfoEXT -> IO b
f Ptr SwapchainPresentModeInfoEXT
p)
  pokeCStruct :: forall b.
Ptr SwapchainPresentModeInfoEXT
-> SwapchainPresentModeInfoEXT -> IO b -> IO b
pokeCStruct Ptr SwapchainPresentModeInfoEXT
p SwapchainPresentModeInfoEXT{Vector PresentModeKHR
presentModes :: Vector PresentModeKHR
$sel:presentModes:SwapchainPresentModeInfoEXT :: SwapchainPresentModeInfoEXT -> Vector PresentModeKHR
..} IO b
f = forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SwapchainPresentModeInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SWAPCHAIN_PRESENT_MODE_INFO_EXT)
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SwapchainPresentModeInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SwapchainPresentModeInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) ((forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Vector a -> Int
Data.Vector.length forall a b. (a -> b) -> a -> b
$ (Vector PresentModeKHR
presentModes)) :: Word32))
    Ptr PresentModeKHR
pPPresentModes' <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes @PresentModeKHR ((forall a. Vector a -> Int
Data.Vector.length (Vector PresentModeKHR
presentModes)) forall a. Num a => a -> a -> a
* Int
4)
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\Int
i PresentModeKHR
e -> forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr PresentModeKHR
pPPresentModes' forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
4 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr PresentModeKHR) (PresentModeKHR
e)) (Vector PresentModeKHR
presentModes)
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SwapchainPresentModeInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (Ptr PresentModeKHR))) (Ptr PresentModeKHR
pPPresentModes')
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = Int
32
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b. Ptr SwapchainPresentModeInfoEXT -> IO b -> IO b
pokeZeroCStruct Ptr SwapchainPresentModeInfoEXT
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SwapchainPresentModeInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SWAPCHAIN_PRESENT_MODE_INFO_EXT)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SwapchainPresentModeInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    IO b
f
instance FromCStruct SwapchainPresentModeInfoEXT where
  peekCStruct :: Ptr SwapchainPresentModeInfoEXT -> IO SwapchainPresentModeInfoEXT
peekCStruct Ptr SwapchainPresentModeInfoEXT
p = do
    Word32
swapchainCount <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr SwapchainPresentModeInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32))
    Ptr PresentModeKHR
pPresentModes <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr PresentModeKHR) ((Ptr SwapchainPresentModeInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (Ptr PresentModeKHR)))
    Vector PresentModeKHR
pPresentModes' <- forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
swapchainCount) (\Int
i -> forall a. Storable a => Ptr a -> IO a
peek @PresentModeKHR ((Ptr PresentModeKHR
pPresentModes forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
4 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr PresentModeKHR)))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Vector PresentModeKHR -> SwapchainPresentModeInfoEXT
SwapchainPresentModeInfoEXT
             Vector PresentModeKHR
pPresentModes'
instance Zero SwapchainPresentModeInfoEXT where
  zero :: SwapchainPresentModeInfoEXT
zero = Vector PresentModeKHR -> SwapchainPresentModeInfoEXT
SwapchainPresentModeInfoEXT
           forall a. Monoid a => a
mempty
data SwapchainPresentScalingCreateInfoEXT = SwapchainPresentScalingCreateInfoEXT
  { 
    
    SwapchainPresentScalingCreateInfoEXT -> PresentScalingFlagsEXT
scalingBehavior :: PresentScalingFlagsEXT
  , 
    
    
    
    SwapchainPresentScalingCreateInfoEXT -> PresentGravityFlagsEXT
presentGravityX :: PresentGravityFlagsEXT
  , 
    
    
    
    SwapchainPresentScalingCreateInfoEXT -> PresentGravityFlagsEXT
presentGravityY :: PresentGravityFlagsEXT
  }
  deriving (Typeable, SwapchainPresentScalingCreateInfoEXT
-> SwapchainPresentScalingCreateInfoEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SwapchainPresentScalingCreateInfoEXT
-> SwapchainPresentScalingCreateInfoEXT -> Bool
$c/= :: SwapchainPresentScalingCreateInfoEXT
-> SwapchainPresentScalingCreateInfoEXT -> Bool
== :: SwapchainPresentScalingCreateInfoEXT
-> SwapchainPresentScalingCreateInfoEXT -> Bool
$c== :: SwapchainPresentScalingCreateInfoEXT
-> SwapchainPresentScalingCreateInfoEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (SwapchainPresentScalingCreateInfoEXT)
#endif
deriving instance Show SwapchainPresentScalingCreateInfoEXT
instance ToCStruct SwapchainPresentScalingCreateInfoEXT where
  withCStruct :: forall b.
SwapchainPresentScalingCreateInfoEXT
-> (Ptr SwapchainPresentScalingCreateInfoEXT -> IO b) -> IO b
withCStruct SwapchainPresentScalingCreateInfoEXT
x Ptr SwapchainPresentScalingCreateInfoEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 forall a b. (a -> b) -> a -> b
$ \Ptr SwapchainPresentScalingCreateInfoEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr SwapchainPresentScalingCreateInfoEXT
p SwapchainPresentScalingCreateInfoEXT
x (Ptr SwapchainPresentScalingCreateInfoEXT -> IO b
f Ptr SwapchainPresentScalingCreateInfoEXT
p)
  pokeCStruct :: forall b.
Ptr SwapchainPresentScalingCreateInfoEXT
-> SwapchainPresentScalingCreateInfoEXT -> IO b -> IO b
pokeCStruct Ptr SwapchainPresentScalingCreateInfoEXT
p SwapchainPresentScalingCreateInfoEXT{PresentGravityFlagsEXT
PresentScalingFlagsEXT
presentGravityY :: PresentGravityFlagsEXT
presentGravityX :: PresentGravityFlagsEXT
scalingBehavior :: PresentScalingFlagsEXT
$sel:presentGravityY:SwapchainPresentScalingCreateInfoEXT :: SwapchainPresentScalingCreateInfoEXT -> PresentGravityFlagsEXT
$sel:presentGravityX:SwapchainPresentScalingCreateInfoEXT :: SwapchainPresentScalingCreateInfoEXT -> PresentGravityFlagsEXT
$sel:scalingBehavior:SwapchainPresentScalingCreateInfoEXT :: SwapchainPresentScalingCreateInfoEXT -> PresentScalingFlagsEXT
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SwapchainPresentScalingCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SWAPCHAIN_PRESENT_SCALING_CREATE_INFO_EXT)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SwapchainPresentScalingCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SwapchainPresentScalingCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr PresentScalingFlagsEXT)) (PresentScalingFlagsEXT
scalingBehavior)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SwapchainPresentScalingCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr PresentGravityFlagsEXT)) (PresentGravityFlagsEXT
presentGravityX)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SwapchainPresentScalingCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr PresentGravityFlagsEXT)) (PresentGravityFlagsEXT
presentGravityY)
    IO b
f
  cStructSize :: Int
cStructSize = Int
32
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b. Ptr SwapchainPresentScalingCreateInfoEXT -> IO b -> IO b
pokeZeroCStruct Ptr SwapchainPresentScalingCreateInfoEXT
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SwapchainPresentScalingCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SWAPCHAIN_PRESENT_SCALING_CREATE_INFO_EXT)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SwapchainPresentScalingCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    IO b
f
instance FromCStruct SwapchainPresentScalingCreateInfoEXT where
  peekCStruct :: Ptr SwapchainPresentScalingCreateInfoEXT
-> IO SwapchainPresentScalingCreateInfoEXT
peekCStruct Ptr SwapchainPresentScalingCreateInfoEXT
p = do
    PresentScalingFlagsEXT
scalingBehavior <- forall a. Storable a => Ptr a -> IO a
peek @PresentScalingFlagsEXT ((Ptr SwapchainPresentScalingCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr PresentScalingFlagsEXT))
    PresentGravityFlagsEXT
presentGravityX <- forall a. Storable a => Ptr a -> IO a
peek @PresentGravityFlagsEXT ((Ptr SwapchainPresentScalingCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr PresentGravityFlagsEXT))
    PresentGravityFlagsEXT
presentGravityY <- forall a. Storable a => Ptr a -> IO a
peek @PresentGravityFlagsEXT ((Ptr SwapchainPresentScalingCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr PresentGravityFlagsEXT))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ PresentScalingFlagsEXT
-> PresentGravityFlagsEXT
-> PresentGravityFlagsEXT
-> SwapchainPresentScalingCreateInfoEXT
SwapchainPresentScalingCreateInfoEXT
             PresentScalingFlagsEXT
scalingBehavior PresentGravityFlagsEXT
presentGravityX PresentGravityFlagsEXT
presentGravityY
instance Storable SwapchainPresentScalingCreateInfoEXT where
  sizeOf :: SwapchainPresentScalingCreateInfoEXT -> Int
sizeOf ~SwapchainPresentScalingCreateInfoEXT
_ = Int
32
  alignment :: SwapchainPresentScalingCreateInfoEXT -> Int
alignment ~SwapchainPresentScalingCreateInfoEXT
_ = Int
8
  peek :: Ptr SwapchainPresentScalingCreateInfoEXT
-> IO SwapchainPresentScalingCreateInfoEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr SwapchainPresentScalingCreateInfoEXT
-> SwapchainPresentScalingCreateInfoEXT -> IO ()
poke Ptr SwapchainPresentScalingCreateInfoEXT
ptr SwapchainPresentScalingCreateInfoEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr SwapchainPresentScalingCreateInfoEXT
ptr SwapchainPresentScalingCreateInfoEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero SwapchainPresentScalingCreateInfoEXT where
  zero :: SwapchainPresentScalingCreateInfoEXT
zero = PresentScalingFlagsEXT
-> PresentGravityFlagsEXT
-> PresentGravityFlagsEXT
-> SwapchainPresentScalingCreateInfoEXT
SwapchainPresentScalingCreateInfoEXT
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
data ReleaseSwapchainImagesInfoEXT = ReleaseSwapchainImagesInfoEXT
  { 
    ReleaseSwapchainImagesInfoEXT -> SwapchainKHR
swapchain :: SwapchainKHR
  , 
    
    ReleaseSwapchainImagesInfoEXT -> Vector Word32
imageIndices :: Vector Word32
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ReleaseSwapchainImagesInfoEXT)
#endif
deriving instance Show ReleaseSwapchainImagesInfoEXT
instance ToCStruct ReleaseSwapchainImagesInfoEXT where
  withCStruct :: forall b.
ReleaseSwapchainImagesInfoEXT
-> (("pReleaseInfo" ::: Ptr ReleaseSwapchainImagesInfoEXT) -> IO b)
-> IO b
withCStruct ReleaseSwapchainImagesInfoEXT
x ("pReleaseInfo" ::: Ptr ReleaseSwapchainImagesInfoEXT) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
40 forall a b. (a -> b) -> a -> b
$ \"pReleaseInfo" ::: Ptr ReleaseSwapchainImagesInfoEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pReleaseInfo" ::: Ptr ReleaseSwapchainImagesInfoEXT
p ReleaseSwapchainImagesInfoEXT
x (("pReleaseInfo" ::: Ptr ReleaseSwapchainImagesInfoEXT) -> IO b
f "pReleaseInfo" ::: Ptr ReleaseSwapchainImagesInfoEXT
p)
  pokeCStruct :: forall b.
("pReleaseInfo" ::: Ptr ReleaseSwapchainImagesInfoEXT)
-> ReleaseSwapchainImagesInfoEXT -> IO b -> IO b
pokeCStruct "pReleaseInfo" ::: Ptr ReleaseSwapchainImagesInfoEXT
p ReleaseSwapchainImagesInfoEXT{Vector Word32
SwapchainKHR
imageIndices :: Vector Word32
swapchain :: SwapchainKHR
$sel:imageIndices:ReleaseSwapchainImagesInfoEXT :: ReleaseSwapchainImagesInfoEXT -> Vector Word32
$sel:swapchain:ReleaseSwapchainImagesInfoEXT :: ReleaseSwapchainImagesInfoEXT -> SwapchainKHR
..} IO b
f = forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke (("pReleaseInfo" ::: Ptr ReleaseSwapchainImagesInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_RELEASE_SWAPCHAIN_IMAGES_INFO_EXT)
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke (("pReleaseInfo" ::: Ptr ReleaseSwapchainImagesInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke (("pReleaseInfo" ::: Ptr ReleaseSwapchainImagesInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr SwapchainKHR)) (SwapchainKHR
swapchain)
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke (("pReleaseInfo" ::: Ptr ReleaseSwapchainImagesInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word32)) ((forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Vector a -> Int
Data.Vector.length forall a b. (a -> b) -> a -> b
$ (Vector Word32
imageIndices)) :: Word32))
    Ptr Word32
pPImageIndices' <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes @Word32 ((forall a. Vector a -> Int
Data.Vector.length (Vector Word32
imageIndices)) forall a. Num a => a -> a -> a
* Int
4)
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\Int
i Word32
e -> forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Word32
pPImageIndices' forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
4 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32) (Word32
e)) (Vector Word32
imageIndices)
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke (("pReleaseInfo" ::: Ptr ReleaseSwapchainImagesInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr (Ptr Word32))) (Ptr Word32
pPImageIndices')
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = Int
40
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
("pReleaseInfo" ::: Ptr ReleaseSwapchainImagesInfoEXT)
-> IO b -> IO b
pokeZeroCStruct "pReleaseInfo" ::: Ptr ReleaseSwapchainImagesInfoEXT
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pReleaseInfo" ::: Ptr ReleaseSwapchainImagesInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_RELEASE_SWAPCHAIN_IMAGES_INFO_EXT)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pReleaseInfo" ::: Ptr ReleaseSwapchainImagesInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pReleaseInfo" ::: Ptr ReleaseSwapchainImagesInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr SwapchainKHR)) (forall a. Zero a => a
zero)
    IO b
f
instance FromCStruct ReleaseSwapchainImagesInfoEXT where
  peekCStruct :: ("pReleaseInfo" ::: Ptr ReleaseSwapchainImagesInfoEXT)
-> IO ReleaseSwapchainImagesInfoEXT
peekCStruct "pReleaseInfo" ::: Ptr ReleaseSwapchainImagesInfoEXT
p = do
    SwapchainKHR
swapchain <- forall a. Storable a => Ptr a -> IO a
peek @SwapchainKHR (("pReleaseInfo" ::: Ptr ReleaseSwapchainImagesInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr SwapchainKHR))
    Word32
imageIndexCount <- forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pReleaseInfo" ::: Ptr ReleaseSwapchainImagesInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word32))
    Ptr Word32
pImageIndices <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr Word32) (("pReleaseInfo" ::: Ptr ReleaseSwapchainImagesInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr (Ptr Word32)))
    Vector Word32
pImageIndices' <- forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
imageIndexCount) (\Int
i -> forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr Word32
pImageIndices forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
4 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32)))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ SwapchainKHR -> Vector Word32 -> ReleaseSwapchainImagesInfoEXT
ReleaseSwapchainImagesInfoEXT
             SwapchainKHR
swapchain Vector Word32
pImageIndices'
instance Zero ReleaseSwapchainImagesInfoEXT where
  zero :: ReleaseSwapchainImagesInfoEXT
zero = SwapchainKHR -> Vector Word32 -> ReleaseSwapchainImagesInfoEXT
ReleaseSwapchainImagesInfoEXT
           forall a. Zero a => a
zero
           forall a. Monoid a => a
mempty
type EXT_SWAPCHAIN_MAINTENANCE_1_SPEC_VERSION = 1
pattern EXT_SWAPCHAIN_MAINTENANCE_1_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_SWAPCHAIN_MAINTENANCE_1_SPEC_VERSION :: forall a. Integral a => a
$mEXT_SWAPCHAIN_MAINTENANCE_1_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_SWAPCHAIN_MAINTENANCE_1_SPEC_VERSION = 1
type EXT_SWAPCHAIN_MAINTENANCE_1_EXTENSION_NAME = "VK_EXT_swapchain_maintenance1"
pattern EXT_SWAPCHAIN_MAINTENANCE_1_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_SWAPCHAIN_MAINTENANCE_1_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mEXT_SWAPCHAIN_MAINTENANCE_1_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_SWAPCHAIN_MAINTENANCE_1_EXTENSION_NAME = "VK_EXT_swapchain_maintenance1"