{-# language CPP #-}
module Vulkan.Core10.Pass  ( createFramebuffer
                           , withFramebuffer
                           , destroyFramebuffer
                           , createRenderPass
                           , withRenderPass
                           , destroyRenderPass
                           , getRenderAreaGranularity
                           , AttachmentDescription(..)
                           , AttachmentReference(..)
                           , SubpassDescription(..)
                           , SubpassDependency(..)
                           , RenderPassCreateInfo(..)
                           , FramebufferCreateInfo(..)
                           ) where
import Control.Exception.Base (bracket)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Data.Typeable (eqT)
import Foreign.Marshal.Alloc (allocaBytesAligned)
import Foreign.Marshal.Alloc (callocBytes)
import Foreign.Marshal.Alloc (free)
import Foreign.Marshal.Utils (maybePeek)
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 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 qualified Data.Vector (null)
import Control.Monad.IO.Class (MonadIO)
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.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.NamedType ((:::))
import Vulkan.Core10.Enums.AccessFlagBits (AccessFlags)
import Vulkan.Core10.AllocationCallbacks (AllocationCallbacks)
import Vulkan.Core10.Enums.AttachmentDescriptionFlagBits (AttachmentDescriptionFlags)
import Vulkan.Core10.Enums.AttachmentLoadOp (AttachmentLoadOp)
import Vulkan.Core10.Enums.AttachmentStoreOp (AttachmentStoreOp)
import Vulkan.CStruct.Extends (Chain)
import Vulkan.Core10.Enums.DependencyFlagBits (DependencyFlags)
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Dynamic (DeviceCmds(pVkCreateFramebuffer))
import Vulkan.Dynamic (DeviceCmds(pVkCreateRenderPass))
import Vulkan.Dynamic (DeviceCmds(pVkDestroyFramebuffer))
import Vulkan.Dynamic (DeviceCmds(pVkDestroyRenderPass))
import Vulkan.Dynamic (DeviceCmds(pVkGetRenderAreaGranularity))
import Vulkan.Core10.Handles (Device_T)
import Vulkan.CStruct.Extends (Extends)
import Vulkan.CStruct.Extends (Extendss)
import Vulkan.CStruct.Extends (Extensible(..))
import Vulkan.Core10.SharedTypes (Extent2D)
import Vulkan.Core10.Enums.Format (Format)
import Vulkan.Core10.Handles (Framebuffer)
import Vulkan.Core10.Handles (Framebuffer(..))
import {-# SOURCE #-} Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer (FramebufferAttachmentsCreateInfo)
import Vulkan.Core10.Enums.FramebufferCreateFlagBits (FramebufferCreateFlags)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.Enums.ImageLayout (ImageLayout)
import Vulkan.Core10.Handles (ImageView)
import Vulkan.CStruct.Extends (PeekChain)
import Vulkan.CStruct.Extends (PeekChain(..))
import Vulkan.Core10.Enums.PipelineBindPoint (PipelineBindPoint)
import Vulkan.Core10.Enums.PipelineStageFlagBits (PipelineStageFlags)
import Vulkan.CStruct.Extends (PokeChain)
import Vulkan.CStruct.Extends (PokeChain(..))
import Vulkan.Core10.Handles (RenderPass)
import Vulkan.Core10.Handles (RenderPass(..))
import Vulkan.Core10.Enums.RenderPassCreateFlagBits (RenderPassCreateFlags)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_fragment_density_map (RenderPassFragmentDensityMapCreateInfoEXT)
import {-# SOURCE #-} Vulkan.Core11.Promoted_From_VK_KHR_maintenance2 (RenderPassInputAttachmentAspectCreateInfo)
import {-# SOURCE #-} Vulkan.Core11.Promoted_From_VK_KHR_multiview (RenderPassMultiviewCreateInfo)
import Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.Core10.Enums.SampleCountFlagBits (SampleCountFlagBits)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.SubpassDescriptionFlagBits (SubpassDescriptionFlags)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Exception (VulkanException(..))
import Vulkan.Zero (Zero(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_FRAMEBUFFER_CREATE_INFO))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_RENDER_PASS_CREATE_INFO))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCreateFramebuffer
  :: FunPtr (Ptr Device_T -> Ptr (FramebufferCreateInfo a) -> Ptr AllocationCallbacks -> Ptr Framebuffer -> IO Result) -> Ptr Device_T -> Ptr (FramebufferCreateInfo a) -> Ptr AllocationCallbacks -> Ptr Framebuffer -> IO Result
createFramebuffer :: forall a io . (Extendss FramebufferCreateInfo a, PokeChain a, MonadIO io) => Device -> FramebufferCreateInfo a -> ("allocator" ::: Maybe AllocationCallbacks) -> io (Framebuffer)
createFramebuffer :: Device
-> FramebufferCreateInfo a
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io Framebuffer
createFramebuffer device :: Device
device createInfo :: FramebufferCreateInfo a
createInfo allocator :: "allocator" ::: Maybe AllocationCallbacks
allocator = IO Framebuffer -> io Framebuffer
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Framebuffer -> io Framebuffer)
-> (ContT Framebuffer IO Framebuffer -> IO Framebuffer)
-> ContT Framebuffer IO Framebuffer
-> io Framebuffer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT Framebuffer IO Framebuffer -> IO Framebuffer
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT Framebuffer IO Framebuffer -> io Framebuffer)
-> ContT Framebuffer IO Framebuffer -> io Framebuffer
forall a b. (a -> b) -> a -> b
$ do
  let vkCreateFramebufferPtr :: FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr (FramebufferCreateInfo a))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pFramebuffer" ::: Ptr Framebuffer)
   -> IO Result)
vkCreateFramebufferPtr = DeviceCmds
-> forall (a :: [*]).
   FunPtr
     (Ptr Device_T
      -> ("pCreateInfo" ::: Ptr (FramebufferCreateInfo a))
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> ("pFramebuffer" ::: Ptr Framebuffer)
      -> IO Result)
pVkCreateFramebuffer (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  IO () -> ContT Framebuffer IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT Framebuffer IO ())
-> IO () -> ContT Framebuffer 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 (FramebufferCreateInfo a))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pFramebuffer" ::: Ptr Framebuffer)
   -> IO Result)
vkCreateFramebufferPtr FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr (FramebufferCreateInfo a))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pFramebuffer" ::: Ptr Framebuffer)
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> ("pCreateInfo" ::: Ptr (FramebufferCreateInfo a))
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> ("pFramebuffer" ::: Ptr Framebuffer)
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr (FramebufferCreateInfo a))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pFramebuffer" ::: Ptr Framebuffer)
   -> IO Result)
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkCreateFramebuffer is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCreateFramebuffer' :: Ptr Device_T
-> ("pCreateInfo" ::: Ptr (FramebufferCreateInfo a))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pFramebuffer" ::: Ptr Framebuffer)
-> IO Result
vkCreateFramebuffer' = FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr (FramebufferCreateInfo a))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pFramebuffer" ::: Ptr Framebuffer)
   -> IO Result)
-> Ptr Device_T
-> ("pCreateInfo" ::: Ptr (FramebufferCreateInfo a))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pFramebuffer" ::: Ptr Framebuffer)
-> IO Result
forall (a :: [*]).
FunPtr
  (Ptr Device_T
   -> Ptr (FramebufferCreateInfo a)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pFramebuffer" ::: Ptr Framebuffer)
   -> IO Result)
-> Ptr Device_T
-> Ptr (FramebufferCreateInfo a)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pFramebuffer" ::: Ptr Framebuffer)
-> IO Result
mkVkCreateFramebuffer FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr (FramebufferCreateInfo a))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pFramebuffer" ::: Ptr Framebuffer)
   -> IO Result)
vkCreateFramebufferPtr
  "pCreateInfo" ::: Ptr (FramebufferCreateInfo a)
pCreateInfo <- ((("pCreateInfo" ::: Ptr (FramebufferCreateInfo a))
  -> IO Framebuffer)
 -> IO Framebuffer)
-> ContT
     Framebuffer IO ("pCreateInfo" ::: Ptr (FramebufferCreateInfo a))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pCreateInfo" ::: Ptr (FramebufferCreateInfo a))
   -> IO Framebuffer)
  -> IO Framebuffer)
 -> ContT
      Framebuffer IO ("pCreateInfo" ::: Ptr (FramebufferCreateInfo a)))
-> ((("pCreateInfo" ::: Ptr (FramebufferCreateInfo a))
     -> IO Framebuffer)
    -> IO Framebuffer)
-> ContT
     Framebuffer IO ("pCreateInfo" ::: Ptr (FramebufferCreateInfo a))
forall a b. (a -> b) -> a -> b
$ FramebufferCreateInfo a
-> (("pCreateInfo" ::: Ptr (FramebufferCreateInfo a))
    -> IO Framebuffer)
-> IO Framebuffer
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (FramebufferCreateInfo a
createInfo)
  "pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
    Nothing -> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ContT Framebuffer IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall (f :: * -> *) a. Applicative f => a -> f a
pure "pAllocator" ::: Ptr AllocationCallbacks
forall a. Ptr a
nullPtr
    Just j :: AllocationCallbacks
j -> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO Framebuffer)
 -> IO Framebuffer)
-> ContT Framebuffer 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 Framebuffer)
  -> IO Framebuffer)
 -> ContT Framebuffer IO ("pAllocator" ::: Ptr AllocationCallbacks))
-> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO Framebuffer)
    -> IO Framebuffer)
-> ContT Framebuffer IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall a b. (a -> b) -> a -> b
$ AllocationCallbacks
-> (("pAllocator" ::: Ptr AllocationCallbacks) -> IO Framebuffer)
-> IO Framebuffer
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
  "pFramebuffer" ::: Ptr Framebuffer
pPFramebuffer <- ((("pFramebuffer" ::: Ptr Framebuffer) -> IO Framebuffer)
 -> IO Framebuffer)
-> ContT Framebuffer IO ("pFramebuffer" ::: Ptr Framebuffer)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pFramebuffer" ::: Ptr Framebuffer) -> IO Framebuffer)
  -> IO Framebuffer)
 -> ContT Framebuffer IO ("pFramebuffer" ::: Ptr Framebuffer))
-> ((("pFramebuffer" ::: Ptr Framebuffer) -> IO Framebuffer)
    -> IO Framebuffer)
-> ContT Framebuffer IO ("pFramebuffer" ::: Ptr Framebuffer)
forall a b. (a -> b) -> a -> b
$ IO ("pFramebuffer" ::: Ptr Framebuffer)
-> (("pFramebuffer" ::: Ptr Framebuffer) -> IO ())
-> (("pFramebuffer" ::: Ptr Framebuffer) -> IO Framebuffer)
-> IO Framebuffer
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pFramebuffer" ::: Ptr Framebuffer)
forall a. Int -> IO (Ptr a)
callocBytes @Framebuffer 8) ("pFramebuffer" ::: Ptr Framebuffer) -> IO ()
forall a. Ptr a -> IO ()
free
  Result
r <- IO Result -> ContT Framebuffer IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT Framebuffer IO Result)
-> IO Result -> ContT Framebuffer IO Result
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> ("pCreateInfo" ::: Ptr (FramebufferCreateInfo a))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pFramebuffer" ::: Ptr Framebuffer)
-> IO Result
vkCreateFramebuffer' (Device -> Ptr Device_T
deviceHandle (Device
device)) "pCreateInfo" ::: Ptr (FramebufferCreateInfo a)
pCreateInfo "pAllocator" ::: Ptr AllocationCallbacks
pAllocator ("pFramebuffer" ::: Ptr Framebuffer
pPFramebuffer)
  IO () -> ContT Framebuffer IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT Framebuffer IO ())
-> IO () -> ContT Framebuffer 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))
  Framebuffer
pFramebuffer <- IO Framebuffer -> ContT Framebuffer IO Framebuffer
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Framebuffer -> ContT Framebuffer IO Framebuffer)
-> IO Framebuffer -> ContT Framebuffer IO Framebuffer
forall a b. (a -> b) -> a -> b
$ ("pFramebuffer" ::: Ptr Framebuffer) -> IO Framebuffer
forall a. Storable a => Ptr a -> IO a
peek @Framebuffer "pFramebuffer" ::: Ptr Framebuffer
pPFramebuffer
  Framebuffer -> ContT Framebuffer IO Framebuffer
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Framebuffer -> ContT Framebuffer IO Framebuffer)
-> Framebuffer -> ContT Framebuffer IO Framebuffer
forall a b. (a -> b) -> a -> b
$ (Framebuffer
pFramebuffer)
withFramebuffer :: forall a io r . (Extendss FramebufferCreateInfo a, PokeChain a, MonadIO io) => Device -> FramebufferCreateInfo a -> Maybe AllocationCallbacks -> (io (Framebuffer) -> ((Framebuffer) -> io ()) -> r) -> r
withFramebuffer :: Device
-> FramebufferCreateInfo a
-> ("allocator" ::: Maybe AllocationCallbacks)
-> (io Framebuffer -> (Framebuffer -> io ()) -> r)
-> r
withFramebuffer device :: Device
device pCreateInfo :: FramebufferCreateInfo a
pCreateInfo pAllocator :: "allocator" ::: Maybe AllocationCallbacks
pAllocator b :: io Framebuffer -> (Framebuffer -> io ()) -> r
b =
  io Framebuffer -> (Framebuffer -> io ()) -> r
b (Device
-> FramebufferCreateInfo a
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io Framebuffer
forall (a :: [*]) (io :: * -> *).
(Extendss FramebufferCreateInfo a, PokeChain a, MonadIO io) =>
Device
-> FramebufferCreateInfo a
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io Framebuffer
createFramebuffer Device
device FramebufferCreateInfo a
pCreateInfo "allocator" ::: Maybe AllocationCallbacks
pAllocator)
    (\(Framebuffer
o0) -> Device
-> Framebuffer
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ()
forall (io :: * -> *).
MonadIO io =>
Device
-> Framebuffer
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ()
destroyFramebuffer Device
device Framebuffer
o0 "allocator" ::: Maybe AllocationCallbacks
pAllocator)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkDestroyFramebuffer
  :: FunPtr (Ptr Device_T -> Framebuffer -> Ptr AllocationCallbacks -> IO ()) -> Ptr Device_T -> Framebuffer -> Ptr AllocationCallbacks -> IO ()
destroyFramebuffer :: forall io . MonadIO io => Device -> Framebuffer -> ("allocator" ::: Maybe AllocationCallbacks) -> io ()
destroyFramebuffer :: Device
-> Framebuffer
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ()
destroyFramebuffer device :: Device
device framebuffer :: Framebuffer
framebuffer allocator :: "allocator" ::: Maybe AllocationCallbacks
allocator = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (ContT () IO () -> IO ()) -> ContT () IO () -> io ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT () IO () -> IO ()
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkDestroyFramebufferPtr :: FunPtr
  (Ptr Device_T
   -> Framebuffer
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
vkDestroyFramebufferPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> Framebuffer
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> IO ())
pVkDestroyFramebuffer (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> Framebuffer
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
vkDestroyFramebufferPtr FunPtr
  (Ptr Device_T
   -> Framebuffer
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
-> FunPtr
     (Ptr Device_T
      -> Framebuffer
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> Framebuffer
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkDestroyFramebuffer is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkDestroyFramebuffer' :: Ptr Device_T
-> Framebuffer
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ()
vkDestroyFramebuffer' = FunPtr
  (Ptr Device_T
   -> Framebuffer
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
-> Ptr Device_T
-> Framebuffer
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ()
mkVkDestroyFramebuffer FunPtr
  (Ptr Device_T
   -> Framebuffer
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
vkDestroyFramebufferPtr
  "pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
    Nothing -> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall (f :: * -> *) a. Applicative f => a -> f a
pure "pAllocator" ::: Ptr AllocationCallbacks
forall a. Ptr a
nullPtr
    Just j :: AllocationCallbacks
j -> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ())
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ())
 -> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks))
-> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ())
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall a b. (a -> b) -> a -> b
$ AllocationCallbacks
-> (("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> Framebuffer
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ()
vkDestroyFramebuffer' (Device -> Ptr Device_T
deviceHandle (Device
device)) (Framebuffer
framebuffer) "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" mkVkCreateRenderPass
  :: FunPtr (Ptr Device_T -> Ptr (RenderPassCreateInfo a) -> Ptr AllocationCallbacks -> Ptr RenderPass -> IO Result) -> Ptr Device_T -> Ptr (RenderPassCreateInfo a) -> Ptr AllocationCallbacks -> Ptr RenderPass -> IO Result
createRenderPass :: forall a io . (Extendss RenderPassCreateInfo a, PokeChain a, MonadIO io) => Device -> RenderPassCreateInfo a -> ("allocator" ::: Maybe AllocationCallbacks) -> io (RenderPass)
createRenderPass :: Device
-> RenderPassCreateInfo a
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io RenderPass
createRenderPass device :: Device
device createInfo :: RenderPassCreateInfo a
createInfo allocator :: "allocator" ::: Maybe AllocationCallbacks
allocator = IO RenderPass -> io RenderPass
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO RenderPass -> io RenderPass)
-> (ContT RenderPass IO RenderPass -> IO RenderPass)
-> ContT RenderPass IO RenderPass
-> io RenderPass
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT RenderPass IO RenderPass -> IO RenderPass
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT RenderPass IO RenderPass -> io RenderPass)
-> ContT RenderPass IO RenderPass -> io RenderPass
forall a b. (a -> b) -> a -> b
$ do
  let vkCreateRenderPassPtr :: FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr (RenderPassCreateInfo a))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pRenderPass" ::: Ptr RenderPass)
   -> IO Result)
vkCreateRenderPassPtr = DeviceCmds
-> forall (a :: [*]).
   FunPtr
     (Ptr Device_T
      -> ("pCreateInfo" ::: Ptr (RenderPassCreateInfo a))
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> ("pRenderPass" ::: Ptr RenderPass)
      -> IO Result)
pVkCreateRenderPass (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  IO () -> ContT RenderPass IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT RenderPass IO ())
-> IO () -> ContT RenderPass 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 (RenderPassCreateInfo a))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pRenderPass" ::: Ptr RenderPass)
   -> IO Result)
vkCreateRenderPassPtr FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr (RenderPassCreateInfo a))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pRenderPass" ::: Ptr RenderPass)
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> ("pCreateInfo" ::: Ptr (RenderPassCreateInfo a))
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> ("pRenderPass" ::: Ptr RenderPass)
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr (RenderPassCreateInfo a))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pRenderPass" ::: Ptr RenderPass)
   -> IO Result)
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkCreateRenderPass is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCreateRenderPass' :: Ptr Device_T
-> ("pCreateInfo" ::: Ptr (RenderPassCreateInfo a))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pRenderPass" ::: Ptr RenderPass)
-> IO Result
vkCreateRenderPass' = FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr (RenderPassCreateInfo a))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pRenderPass" ::: Ptr RenderPass)
   -> IO Result)
-> Ptr Device_T
-> ("pCreateInfo" ::: Ptr (RenderPassCreateInfo a))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pRenderPass" ::: Ptr RenderPass)
-> IO Result
forall (a :: [*]).
FunPtr
  (Ptr Device_T
   -> Ptr (RenderPassCreateInfo a)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pRenderPass" ::: Ptr RenderPass)
   -> IO Result)
-> Ptr Device_T
-> Ptr (RenderPassCreateInfo a)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pRenderPass" ::: Ptr RenderPass)
-> IO Result
mkVkCreateRenderPass FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr (RenderPassCreateInfo a))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pRenderPass" ::: Ptr RenderPass)
   -> IO Result)
vkCreateRenderPassPtr
  "pCreateInfo" ::: Ptr (RenderPassCreateInfo a)
pCreateInfo <- ((("pCreateInfo" ::: Ptr (RenderPassCreateInfo a))
  -> IO RenderPass)
 -> IO RenderPass)
-> ContT
     RenderPass IO ("pCreateInfo" ::: Ptr (RenderPassCreateInfo a))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pCreateInfo" ::: Ptr (RenderPassCreateInfo a))
   -> IO RenderPass)
  -> IO RenderPass)
 -> ContT
      RenderPass IO ("pCreateInfo" ::: Ptr (RenderPassCreateInfo a)))
-> ((("pCreateInfo" ::: Ptr (RenderPassCreateInfo a))
     -> IO RenderPass)
    -> IO RenderPass)
-> ContT
     RenderPass IO ("pCreateInfo" ::: Ptr (RenderPassCreateInfo a))
forall a b. (a -> b) -> a -> b
$ RenderPassCreateInfo a
-> (("pCreateInfo" ::: Ptr (RenderPassCreateInfo a))
    -> IO RenderPass)
-> IO RenderPass
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (RenderPassCreateInfo a
createInfo)
  "pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
    Nothing -> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ContT RenderPass IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall (f :: * -> *) a. Applicative f => a -> f a
pure "pAllocator" ::: Ptr AllocationCallbacks
forall a. Ptr a
nullPtr
    Just j :: AllocationCallbacks
j -> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO RenderPass)
 -> IO RenderPass)
-> ContT RenderPass 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 RenderPass)
  -> IO RenderPass)
 -> ContT RenderPass IO ("pAllocator" ::: Ptr AllocationCallbacks))
-> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO RenderPass)
    -> IO RenderPass)
-> ContT RenderPass IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall a b. (a -> b) -> a -> b
$ AllocationCallbacks
-> (("pAllocator" ::: Ptr AllocationCallbacks) -> IO RenderPass)
-> IO RenderPass
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
  "pRenderPass" ::: Ptr RenderPass
pPRenderPass <- ((("pRenderPass" ::: Ptr RenderPass) -> IO RenderPass)
 -> IO RenderPass)
-> ContT RenderPass IO ("pRenderPass" ::: Ptr RenderPass)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pRenderPass" ::: Ptr RenderPass) -> IO RenderPass)
  -> IO RenderPass)
 -> ContT RenderPass IO ("pRenderPass" ::: Ptr RenderPass))
-> ((("pRenderPass" ::: Ptr RenderPass) -> IO RenderPass)
    -> IO RenderPass)
-> ContT RenderPass IO ("pRenderPass" ::: Ptr RenderPass)
forall a b. (a -> b) -> a -> b
$ IO ("pRenderPass" ::: Ptr RenderPass)
-> (("pRenderPass" ::: Ptr RenderPass) -> IO ())
-> (("pRenderPass" ::: Ptr RenderPass) -> IO RenderPass)
-> IO RenderPass
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pRenderPass" ::: Ptr RenderPass)
forall a. Int -> IO (Ptr a)
callocBytes @RenderPass 8) ("pRenderPass" ::: Ptr RenderPass) -> IO ()
forall a. Ptr a -> IO ()
free
  Result
r <- IO Result -> ContT RenderPass IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT RenderPass IO Result)
-> IO Result -> ContT RenderPass IO Result
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> ("pCreateInfo" ::: Ptr (RenderPassCreateInfo a))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pRenderPass" ::: Ptr RenderPass)
-> IO Result
vkCreateRenderPass' (Device -> Ptr Device_T
deviceHandle (Device
device)) "pCreateInfo" ::: Ptr (RenderPassCreateInfo a)
pCreateInfo "pAllocator" ::: Ptr AllocationCallbacks
pAllocator ("pRenderPass" ::: Ptr RenderPass
pPRenderPass)
  IO () -> ContT RenderPass IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT RenderPass IO ())
-> IO () -> ContT RenderPass 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))
  RenderPass
pRenderPass <- IO RenderPass -> ContT RenderPass IO RenderPass
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO RenderPass -> ContT RenderPass IO RenderPass)
-> IO RenderPass -> ContT RenderPass IO RenderPass
forall a b. (a -> b) -> a -> b
$ ("pRenderPass" ::: Ptr RenderPass) -> IO RenderPass
forall a. Storable a => Ptr a -> IO a
peek @RenderPass "pRenderPass" ::: Ptr RenderPass
pPRenderPass
  RenderPass -> ContT RenderPass IO RenderPass
forall (f :: * -> *) a. Applicative f => a -> f a
pure (RenderPass -> ContT RenderPass IO RenderPass)
-> RenderPass -> ContT RenderPass IO RenderPass
forall a b. (a -> b) -> a -> b
$ (RenderPass
pRenderPass)
withRenderPass :: forall a io r . (Extendss RenderPassCreateInfo a, PokeChain a, MonadIO io) => Device -> RenderPassCreateInfo a -> Maybe AllocationCallbacks -> (io (RenderPass) -> ((RenderPass) -> io ()) -> r) -> r
withRenderPass :: Device
-> RenderPassCreateInfo a
-> ("allocator" ::: Maybe AllocationCallbacks)
-> (io RenderPass -> (RenderPass -> io ()) -> r)
-> r
withRenderPass device :: Device
device pCreateInfo :: RenderPassCreateInfo a
pCreateInfo pAllocator :: "allocator" ::: Maybe AllocationCallbacks
pAllocator b :: io RenderPass -> (RenderPass -> io ()) -> r
b =
  io RenderPass -> (RenderPass -> io ()) -> r
b (Device
-> RenderPassCreateInfo a
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io RenderPass
forall (a :: [*]) (io :: * -> *).
(Extendss RenderPassCreateInfo a, PokeChain a, MonadIO io) =>
Device
-> RenderPassCreateInfo a
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io RenderPass
createRenderPass Device
device RenderPassCreateInfo a
pCreateInfo "allocator" ::: Maybe AllocationCallbacks
pAllocator)
    (\(RenderPass
o0) -> Device
-> RenderPass
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ()
forall (io :: * -> *).
MonadIO io =>
Device
-> RenderPass
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ()
destroyRenderPass Device
device RenderPass
o0 "allocator" ::: Maybe AllocationCallbacks
pAllocator)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkDestroyRenderPass
  :: FunPtr (Ptr Device_T -> RenderPass -> Ptr AllocationCallbacks -> IO ()) -> Ptr Device_T -> RenderPass -> Ptr AllocationCallbacks -> IO ()
destroyRenderPass :: forall io . MonadIO io => Device -> RenderPass -> ("allocator" ::: Maybe AllocationCallbacks) -> io ()
destroyRenderPass :: Device
-> RenderPass
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ()
destroyRenderPass device :: Device
device renderPass :: RenderPass
renderPass allocator :: "allocator" ::: Maybe AllocationCallbacks
allocator = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (ContT () IO () -> IO ()) -> ContT () IO () -> io ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT () IO () -> IO ()
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkDestroyRenderPassPtr :: FunPtr
  (Ptr Device_T
   -> RenderPass
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
vkDestroyRenderPassPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> RenderPass
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> IO ())
pVkDestroyRenderPass (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> RenderPass
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
vkDestroyRenderPassPtr FunPtr
  (Ptr Device_T
   -> RenderPass
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
-> FunPtr
     (Ptr Device_T
      -> RenderPass
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> RenderPass
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkDestroyRenderPass is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkDestroyRenderPass' :: Ptr Device_T
-> RenderPass
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ()
vkDestroyRenderPass' = FunPtr
  (Ptr Device_T
   -> RenderPass
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
-> Ptr Device_T
-> RenderPass
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ()
mkVkDestroyRenderPass FunPtr
  (Ptr Device_T
   -> RenderPass
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
vkDestroyRenderPassPtr
  "pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
    Nothing -> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall (f :: * -> *) a. Applicative f => a -> f a
pure "pAllocator" ::: Ptr AllocationCallbacks
forall a. Ptr a
nullPtr
    Just j :: AllocationCallbacks
j -> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ())
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ())
 -> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks))
-> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ())
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall a b. (a -> b) -> a -> b
$ AllocationCallbacks
-> (("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> RenderPass
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ()
vkDestroyRenderPass' (Device -> Ptr Device_T
deviceHandle (Device
device)) (RenderPass
renderPass) "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" mkVkGetRenderAreaGranularity
  :: FunPtr (Ptr Device_T -> RenderPass -> Ptr Extent2D -> IO ()) -> Ptr Device_T -> RenderPass -> Ptr Extent2D -> IO ()
getRenderAreaGranularity :: forall io . MonadIO io => Device -> RenderPass -> io (("granularity" ::: Extent2D))
getRenderAreaGranularity :: Device -> RenderPass -> io ("granularity" ::: Extent2D)
getRenderAreaGranularity device :: Device
device renderPass :: RenderPass
renderPass = IO ("granularity" ::: Extent2D) -> io ("granularity" ::: Extent2D)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ("granularity" ::: Extent2D)
 -> io ("granularity" ::: Extent2D))
-> (ContT
      ("granularity" ::: Extent2D) IO ("granularity" ::: Extent2D)
    -> IO ("granularity" ::: Extent2D))
-> ContT
     ("granularity" ::: Extent2D) IO ("granularity" ::: Extent2D)
-> io ("granularity" ::: Extent2D)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT ("granularity" ::: Extent2D) IO ("granularity" ::: Extent2D)
-> IO ("granularity" ::: Extent2D)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT ("granularity" ::: Extent2D) IO ("granularity" ::: Extent2D)
 -> io ("granularity" ::: Extent2D))
-> ContT
     ("granularity" ::: Extent2D) IO ("granularity" ::: Extent2D)
-> io ("granularity" ::: Extent2D)
forall a b. (a -> b) -> a -> b
$ do
  let vkGetRenderAreaGranularityPtr :: FunPtr
  (Ptr Device_T
   -> RenderPass
   -> ("pGranularity" ::: Ptr ("granularity" ::: Extent2D))
   -> IO ())
vkGetRenderAreaGranularityPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> RenderPass
      -> ("pGranularity" ::: Ptr ("granularity" ::: Extent2D))
      -> IO ())
pVkGetRenderAreaGranularity (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  IO () -> ContT ("granularity" ::: Extent2D) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT ("granularity" ::: Extent2D) IO ())
-> IO () -> ContT ("granularity" ::: Extent2D) IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> RenderPass
   -> ("pGranularity" ::: Ptr ("granularity" ::: Extent2D))
   -> IO ())
vkGetRenderAreaGranularityPtr FunPtr
  (Ptr Device_T
   -> RenderPass
   -> ("pGranularity" ::: Ptr ("granularity" ::: Extent2D))
   -> IO ())
-> FunPtr
     (Ptr Device_T
      -> RenderPass
      -> ("pGranularity" ::: Ptr ("granularity" ::: Extent2D))
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> RenderPass
   -> ("pGranularity" ::: Ptr ("granularity" ::: Extent2D))
   -> IO ())
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkGetRenderAreaGranularity is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetRenderAreaGranularity' :: Ptr Device_T
-> RenderPass
-> ("pGranularity" ::: Ptr ("granularity" ::: Extent2D))
-> IO ()
vkGetRenderAreaGranularity' = FunPtr
  (Ptr Device_T
   -> RenderPass
   -> ("pGranularity" ::: Ptr ("granularity" ::: Extent2D))
   -> IO ())
-> Ptr Device_T
-> RenderPass
-> ("pGranularity" ::: Ptr ("granularity" ::: Extent2D))
-> IO ()
mkVkGetRenderAreaGranularity FunPtr
  (Ptr Device_T
   -> RenderPass
   -> ("pGranularity" ::: Ptr ("granularity" ::: Extent2D))
   -> IO ())
vkGetRenderAreaGranularityPtr
  "pGranularity" ::: Ptr ("granularity" ::: Extent2D)
pPGranularity <- ((("pGranularity" ::: Ptr ("granularity" ::: Extent2D))
  -> IO ("granularity" ::: Extent2D))
 -> IO ("granularity" ::: Extent2D))
-> ContT
     ("granularity" ::: Extent2D)
     IO
     ("pGranularity" ::: Ptr ("granularity" ::: Extent2D))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (forall b.
ToCStruct ("granularity" ::: Extent2D) =>
(("pGranularity" ::: Ptr ("granularity" ::: Extent2D)) -> IO b)
-> IO b
forall a b. ToCStruct a => (Ptr a -> IO b) -> IO b
withZeroCStruct @Extent2D)
  IO () -> ContT ("granularity" ::: Extent2D) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT ("granularity" ::: Extent2D) IO ())
-> IO () -> ContT ("granularity" ::: Extent2D) IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> RenderPass
-> ("pGranularity" ::: Ptr ("granularity" ::: Extent2D))
-> IO ()
vkGetRenderAreaGranularity' (Device -> Ptr Device_T
deviceHandle (Device
device)) (RenderPass
renderPass) ("pGranularity" ::: Ptr ("granularity" ::: Extent2D)
pPGranularity)
  "granularity" ::: Extent2D
pGranularity <- IO ("granularity" ::: Extent2D)
-> ContT
     ("granularity" ::: Extent2D) IO ("granularity" ::: Extent2D)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ("granularity" ::: Extent2D)
 -> ContT
      ("granularity" ::: Extent2D) IO ("granularity" ::: Extent2D))
-> IO ("granularity" ::: Extent2D)
-> ContT
     ("granularity" ::: Extent2D) IO ("granularity" ::: Extent2D)
forall a b. (a -> b) -> a -> b
$ ("pGranularity" ::: Ptr ("granularity" ::: Extent2D))
-> IO ("granularity" ::: Extent2D)
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Extent2D "pGranularity" ::: Ptr ("granularity" ::: Extent2D)
pPGranularity
  ("granularity" ::: Extent2D)
-> ContT
     ("granularity" ::: Extent2D) IO ("granularity" ::: Extent2D)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (("granularity" ::: Extent2D)
 -> ContT
      ("granularity" ::: Extent2D) IO ("granularity" ::: Extent2D))
-> ("granularity" ::: Extent2D)
-> ContT
     ("granularity" ::: Extent2D) IO ("granularity" ::: Extent2D)
forall a b. (a -> b) -> a -> b
$ ("granularity" ::: Extent2D
pGranularity)
data AttachmentDescription = AttachmentDescription
  { 
    
    
    AttachmentDescription -> AttachmentDescriptionFlags
flags :: AttachmentDescriptionFlags
  , 
    
    AttachmentDescription -> Format
format :: Format
  , 
    
    AttachmentDescription -> SampleCountFlagBits
samples :: SampleCountFlagBits
  , 
    
    
    
    AttachmentDescription -> AttachmentLoadOp
loadOp :: AttachmentLoadOp
  , 
    
    
    AttachmentDescription -> AttachmentStoreOp
storeOp :: AttachmentStoreOp
  , 
    
    
    
    AttachmentDescription -> AttachmentLoadOp
stencilLoadOp :: AttachmentLoadOp
  , 
    
    
    
    AttachmentDescription -> AttachmentStoreOp
stencilStoreOp :: AttachmentStoreOp
  , 
    
    AttachmentDescription -> ImageLayout
initialLayout :: ImageLayout
  , 
    
    AttachmentDescription -> ImageLayout
finalLayout :: ImageLayout
  }
  deriving (Typeable)
deriving instance Show AttachmentDescription
instance ToCStruct AttachmentDescription where
  withCStruct :: AttachmentDescription
-> (Ptr AttachmentDescription -> IO b) -> IO b
withCStruct x :: AttachmentDescription
x f :: Ptr AttachmentDescription -> IO b
f = Int -> Int -> (Ptr AttachmentDescription -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 36 4 ((Ptr AttachmentDescription -> IO b) -> IO b)
-> (Ptr AttachmentDescription -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr AttachmentDescription
p -> Ptr AttachmentDescription -> AttachmentDescription -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr AttachmentDescription
p AttachmentDescription
x (Ptr AttachmentDescription -> IO b
f Ptr AttachmentDescription
p)
  pokeCStruct :: Ptr AttachmentDescription -> AttachmentDescription -> IO b -> IO b
pokeCStruct p :: Ptr AttachmentDescription
p AttachmentDescription{..} f :: IO b
f = do
    Ptr AttachmentDescriptionFlags
-> AttachmentDescriptionFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AttachmentDescription
p Ptr AttachmentDescription -> Int -> Ptr AttachmentDescriptionFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr AttachmentDescriptionFlags)) (AttachmentDescriptionFlags
flags)
    Ptr Format -> Format -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AttachmentDescription
p Ptr AttachmentDescription -> Int -> Ptr Format
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Format)) (Format
format)
    Ptr SampleCountFlagBits -> SampleCountFlagBits -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AttachmentDescription
p Ptr AttachmentDescription -> Int -> Ptr SampleCountFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr SampleCountFlagBits)) (SampleCountFlagBits
samples)
    Ptr AttachmentLoadOp -> AttachmentLoadOp -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AttachmentDescription
p Ptr AttachmentDescription -> Int -> Ptr AttachmentLoadOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr AttachmentLoadOp)) (AttachmentLoadOp
loadOp)
    Ptr AttachmentStoreOp -> AttachmentStoreOp -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AttachmentDescription
p Ptr AttachmentDescription -> Int -> Ptr AttachmentStoreOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr AttachmentStoreOp)) (AttachmentStoreOp
storeOp)
    Ptr AttachmentLoadOp -> AttachmentLoadOp -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AttachmentDescription
p Ptr AttachmentDescription -> Int -> Ptr AttachmentLoadOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr AttachmentLoadOp)) (AttachmentLoadOp
stencilLoadOp)
    Ptr AttachmentStoreOp -> AttachmentStoreOp -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AttachmentDescription
p Ptr AttachmentDescription -> Int -> Ptr AttachmentStoreOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr AttachmentStoreOp)) (AttachmentStoreOp
stencilStoreOp)
    Ptr ImageLayout -> ImageLayout -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AttachmentDescription
p Ptr AttachmentDescription -> Int -> Ptr ImageLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr ImageLayout)) (ImageLayout
initialLayout)
    Ptr ImageLayout -> ImageLayout -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AttachmentDescription
p Ptr AttachmentDescription -> Int -> Ptr ImageLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr ImageLayout)) (ImageLayout
finalLayout)
    IO b
f
  cStructSize :: Int
cStructSize = 36
  cStructAlignment :: Int
cStructAlignment = 4
  pokeZeroCStruct :: Ptr AttachmentDescription -> IO b -> IO b
pokeZeroCStruct p :: Ptr AttachmentDescription
p f :: IO b
f = do
    Ptr Format -> Format -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AttachmentDescription
p Ptr AttachmentDescription -> Int -> Ptr Format
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Format)) (Format
forall a. Zero a => a
zero)
    Ptr SampleCountFlagBits -> SampleCountFlagBits -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AttachmentDescription
p Ptr AttachmentDescription -> Int -> Ptr SampleCountFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr SampleCountFlagBits)) (SampleCountFlagBits
forall a. Zero a => a
zero)
    Ptr AttachmentLoadOp -> AttachmentLoadOp -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AttachmentDescription
p Ptr AttachmentDescription -> Int -> Ptr AttachmentLoadOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr AttachmentLoadOp)) (AttachmentLoadOp
forall a. Zero a => a
zero)
    Ptr AttachmentStoreOp -> AttachmentStoreOp -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AttachmentDescription
p Ptr AttachmentDescription -> Int -> Ptr AttachmentStoreOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr AttachmentStoreOp)) (AttachmentStoreOp
forall a. Zero a => a
zero)
    Ptr AttachmentLoadOp -> AttachmentLoadOp -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AttachmentDescription
p Ptr AttachmentDescription -> Int -> Ptr AttachmentLoadOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr AttachmentLoadOp)) (AttachmentLoadOp
forall a. Zero a => a
zero)
    Ptr AttachmentStoreOp -> AttachmentStoreOp -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AttachmentDescription
p Ptr AttachmentDescription -> Int -> Ptr AttachmentStoreOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr AttachmentStoreOp)) (AttachmentStoreOp
forall a. Zero a => a
zero)
    Ptr ImageLayout -> ImageLayout -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AttachmentDescription
p Ptr AttachmentDescription -> Int -> Ptr ImageLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr ImageLayout)) (ImageLayout
forall a. Zero a => a
zero)
    Ptr ImageLayout -> ImageLayout -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AttachmentDescription
p Ptr AttachmentDescription -> Int -> Ptr ImageLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr ImageLayout)) (ImageLayout
forall a. Zero a => a
zero)
    IO b
f
instance FromCStruct AttachmentDescription where
  peekCStruct :: Ptr AttachmentDescription -> IO AttachmentDescription
peekCStruct p :: Ptr AttachmentDescription
p = do
    AttachmentDescriptionFlags
flags <- Ptr AttachmentDescriptionFlags -> IO AttachmentDescriptionFlags
forall a. Storable a => Ptr a -> IO a
peek @AttachmentDescriptionFlags ((Ptr AttachmentDescription
p Ptr AttachmentDescription -> Int -> Ptr AttachmentDescriptionFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr AttachmentDescriptionFlags))
    Format
format <- Ptr Format -> IO Format
forall a. Storable a => Ptr a -> IO a
peek @Format ((Ptr AttachmentDescription
p Ptr AttachmentDescription -> Int -> Ptr Format
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Format))
    SampleCountFlagBits
samples <- Ptr SampleCountFlagBits -> IO SampleCountFlagBits
forall a. Storable a => Ptr a -> IO a
peek @SampleCountFlagBits ((Ptr AttachmentDescription
p Ptr AttachmentDescription -> Int -> Ptr SampleCountFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr SampleCountFlagBits))
    AttachmentLoadOp
loadOp <- Ptr AttachmentLoadOp -> IO AttachmentLoadOp
forall a. Storable a => Ptr a -> IO a
peek @AttachmentLoadOp ((Ptr AttachmentDescription
p Ptr AttachmentDescription -> Int -> Ptr AttachmentLoadOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr AttachmentLoadOp))
    AttachmentStoreOp
storeOp <- Ptr AttachmentStoreOp -> IO AttachmentStoreOp
forall a. Storable a => Ptr a -> IO a
peek @AttachmentStoreOp ((Ptr AttachmentDescription
p Ptr AttachmentDescription -> Int -> Ptr AttachmentStoreOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr AttachmentStoreOp))
    AttachmentLoadOp
stencilLoadOp <- Ptr AttachmentLoadOp -> IO AttachmentLoadOp
forall a. Storable a => Ptr a -> IO a
peek @AttachmentLoadOp ((Ptr AttachmentDescription
p Ptr AttachmentDescription -> Int -> Ptr AttachmentLoadOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr AttachmentLoadOp))
    AttachmentStoreOp
stencilStoreOp <- Ptr AttachmentStoreOp -> IO AttachmentStoreOp
forall a. Storable a => Ptr a -> IO a
peek @AttachmentStoreOp ((Ptr AttachmentDescription
p Ptr AttachmentDescription -> Int -> Ptr AttachmentStoreOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr AttachmentStoreOp))
    ImageLayout
initialLayout <- Ptr ImageLayout -> IO ImageLayout
forall a. Storable a => Ptr a -> IO a
peek @ImageLayout ((Ptr AttachmentDescription
p Ptr AttachmentDescription -> Int -> Ptr ImageLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr ImageLayout))
    ImageLayout
finalLayout <- Ptr ImageLayout -> IO ImageLayout
forall a. Storable a => Ptr a -> IO a
peek @ImageLayout ((Ptr AttachmentDescription
p Ptr AttachmentDescription -> Int -> Ptr ImageLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr ImageLayout))
    AttachmentDescription -> IO AttachmentDescription
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AttachmentDescription -> IO AttachmentDescription)
-> AttachmentDescription -> IO AttachmentDescription
forall a b. (a -> b) -> a -> b
$ AttachmentDescriptionFlags
-> Format
-> SampleCountFlagBits
-> AttachmentLoadOp
-> AttachmentStoreOp
-> AttachmentLoadOp
-> AttachmentStoreOp
-> ImageLayout
-> ImageLayout
-> AttachmentDescription
AttachmentDescription
             AttachmentDescriptionFlags
flags Format
format SampleCountFlagBits
samples AttachmentLoadOp
loadOp AttachmentStoreOp
storeOp AttachmentLoadOp
stencilLoadOp AttachmentStoreOp
stencilStoreOp ImageLayout
initialLayout ImageLayout
finalLayout
instance Storable AttachmentDescription where
  sizeOf :: AttachmentDescription -> Int
sizeOf ~AttachmentDescription
_ = 36
  alignment :: AttachmentDescription -> Int
alignment ~AttachmentDescription
_ = 4
  peek :: Ptr AttachmentDescription -> IO AttachmentDescription
peek = Ptr AttachmentDescription -> IO AttachmentDescription
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr AttachmentDescription -> AttachmentDescription -> IO ()
poke ptr :: Ptr AttachmentDescription
ptr poked :: AttachmentDescription
poked = Ptr AttachmentDescription
-> AttachmentDescription -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr AttachmentDescription
ptr AttachmentDescription
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero AttachmentDescription where
  zero :: AttachmentDescription
zero = AttachmentDescriptionFlags
-> Format
-> SampleCountFlagBits
-> AttachmentLoadOp
-> AttachmentStoreOp
-> AttachmentLoadOp
-> AttachmentStoreOp
-> ImageLayout
-> ImageLayout
-> AttachmentDescription
AttachmentDescription
           AttachmentDescriptionFlags
forall a. Zero a => a
zero
           Format
forall a. Zero a => a
zero
           SampleCountFlagBits
forall a. Zero a => a
zero
           AttachmentLoadOp
forall a. Zero a => a
zero
           AttachmentStoreOp
forall a. Zero a => a
zero
           AttachmentLoadOp
forall a. Zero a => a
zero
           AttachmentStoreOp
forall a. Zero a => a
zero
           ImageLayout
forall a. Zero a => a
zero
           ImageLayout
forall a. Zero a => a
zero
data AttachmentReference = AttachmentReference
  { 
    
    
    
    AttachmentReference -> Word32
attachment :: Word32
  , 
    
    AttachmentReference -> ImageLayout
layout :: ImageLayout
  }
  deriving (Typeable)
deriving instance Show AttachmentReference
instance ToCStruct AttachmentReference where
  withCStruct :: AttachmentReference -> (Ptr AttachmentReference -> IO b) -> IO b
withCStruct x :: AttachmentReference
x f :: Ptr AttachmentReference -> IO b
f = Int -> Int -> (Ptr AttachmentReference -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 8 4 ((Ptr AttachmentReference -> IO b) -> IO b)
-> (Ptr AttachmentReference -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr AttachmentReference
p -> Ptr AttachmentReference -> AttachmentReference -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr AttachmentReference
p AttachmentReference
x (Ptr AttachmentReference -> IO b
f Ptr AttachmentReference
p)
  pokeCStruct :: Ptr AttachmentReference -> AttachmentReference -> IO b -> IO b
pokeCStruct p :: Ptr AttachmentReference
p AttachmentReference{..} f :: IO b
f = do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AttachmentReference
p Ptr AttachmentReference -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32)) (Word32
attachment)
    Ptr ImageLayout -> ImageLayout -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AttachmentReference
p Ptr AttachmentReference -> Int -> Ptr ImageLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr ImageLayout)) (ImageLayout
layout)
    IO b
f
  cStructSize :: Int
cStructSize = 8
  cStructAlignment :: Int
cStructAlignment = 4
  pokeZeroCStruct :: Ptr AttachmentReference -> IO b -> IO b
pokeZeroCStruct p :: Ptr AttachmentReference
p f :: IO b
f = do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AttachmentReference
p Ptr AttachmentReference -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr ImageLayout -> ImageLayout -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AttachmentReference
p Ptr AttachmentReference -> Int -> Ptr ImageLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr ImageLayout)) (ImageLayout
forall a. Zero a => a
zero)
    IO b
f
instance FromCStruct AttachmentReference where
  peekCStruct :: Ptr AttachmentReference -> IO AttachmentReference
peekCStruct p :: Ptr AttachmentReference
p = do
    Word32
attachment <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr AttachmentReference
p Ptr AttachmentReference -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32))
    ImageLayout
layout <- Ptr ImageLayout -> IO ImageLayout
forall a. Storable a => Ptr a -> IO a
peek @ImageLayout ((Ptr AttachmentReference
p Ptr AttachmentReference -> Int -> Ptr ImageLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr ImageLayout))
    AttachmentReference -> IO AttachmentReference
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AttachmentReference -> IO AttachmentReference)
-> AttachmentReference -> IO AttachmentReference
forall a b. (a -> b) -> a -> b
$ Word32 -> ImageLayout -> AttachmentReference
AttachmentReference
             Word32
attachment ImageLayout
layout
instance Storable AttachmentReference where
  sizeOf :: AttachmentReference -> Int
sizeOf ~AttachmentReference
_ = 8
  alignment :: AttachmentReference -> Int
alignment ~AttachmentReference
_ = 4
  peek :: Ptr AttachmentReference -> IO AttachmentReference
peek = Ptr AttachmentReference -> IO AttachmentReference
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr AttachmentReference -> AttachmentReference -> IO ()
poke ptr :: Ptr AttachmentReference
ptr poked :: AttachmentReference
poked = Ptr AttachmentReference -> AttachmentReference -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr AttachmentReference
ptr AttachmentReference
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero AttachmentReference where
  zero :: AttachmentReference
zero = Word32 -> ImageLayout -> AttachmentReference
AttachmentReference
           Word32
forall a. Zero a => a
zero
           ImageLayout
forall a. Zero a => a
zero
data SubpassDescription = SubpassDescription
  { 
    
    
    SubpassDescription -> SubpassDescriptionFlags
flags :: SubpassDescriptionFlags
  , 
    
    
    SubpassDescription -> PipelineBindPoint
pipelineBindPoint :: PipelineBindPoint
  , 
    
    
    SubpassDescription -> Vector AttachmentReference
inputAttachments :: Vector AttachmentReference
  , 
    
    
    SubpassDescription -> Vector AttachmentReference
colorAttachments :: Vector AttachmentReference
  , 
    
    
    SubpassDescription -> Vector AttachmentReference
resolveAttachments :: Vector AttachmentReference
  , 
    
    
    SubpassDescription -> Maybe AttachmentReference
depthStencilAttachment :: Maybe AttachmentReference
  , 
    
    
    
    SubpassDescription -> Vector Word32
preserveAttachments :: Vector Word32
  }
  deriving (Typeable)
deriving instance Show SubpassDescription
instance ToCStruct SubpassDescription where
  withCStruct :: SubpassDescription -> (Ptr SubpassDescription -> IO b) -> IO b
withCStruct x :: SubpassDescription
x f :: Ptr SubpassDescription -> IO b
f = Int -> Int -> (Ptr SubpassDescription -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 72 8 ((Ptr SubpassDescription -> IO b) -> IO b)
-> (Ptr SubpassDescription -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr SubpassDescription
p -> Ptr SubpassDescription -> SubpassDescription -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr SubpassDescription
p SubpassDescription
x (Ptr SubpassDescription -> IO b
f Ptr SubpassDescription
p)
  pokeCStruct :: Ptr SubpassDescription -> SubpassDescription -> IO b -> IO b
pokeCStruct p :: Ptr SubpassDescription
p SubpassDescription{..} f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr SubpassDescriptionFlags -> SubpassDescriptionFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDescription
p Ptr SubpassDescription -> Int -> Ptr SubpassDescriptionFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr SubpassDescriptionFlags)) (SubpassDescriptionFlags
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 PipelineBindPoint -> PipelineBindPoint -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDescription
p Ptr SubpassDescription -> Int -> Ptr PipelineBindPoint
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr PipelineBindPoint)) (PipelineBindPoint
pipelineBindPoint)
    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 Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDescription
p Ptr SubpassDescription -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32)) ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector AttachmentReference -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector AttachmentReference -> Int)
-> Vector AttachmentReference -> Int
forall a b. (a -> b) -> a -> b
$ (Vector AttachmentReference
inputAttachments)) :: Word32))
    Ptr AttachmentReference
pPInputAttachments' <- ((Ptr AttachmentReference -> IO b) -> IO b)
-> ContT b IO (Ptr AttachmentReference)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr AttachmentReference -> IO b) -> IO b)
 -> ContT b IO (Ptr AttachmentReference))
-> ((Ptr AttachmentReference -> IO b) -> IO b)
-> ContT b IO (Ptr AttachmentReference)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr AttachmentReference -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @AttachmentReference ((Vector AttachmentReference -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector AttachmentReference
inputAttachments)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 4
    (Int -> AttachmentReference -> ContT b IO ())
-> Vector AttachmentReference -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: AttachmentReference
e -> ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr AttachmentReference -> AttachmentReference -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr AttachmentReference
pPInputAttachments' Ptr AttachmentReference -> Int -> Ptr AttachmentReference
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr AttachmentReference) (AttachmentReference
e) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())) (Vector AttachmentReference
inputAttachments)
    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 AttachmentReference) -> Ptr AttachmentReference -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDescription
p Ptr SubpassDescription -> Int -> Ptr (Ptr AttachmentReference)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (Ptr AttachmentReference))) (Ptr AttachmentReference
pPInputAttachments')
    let pColorAttachmentsLength :: Int
pColorAttachmentsLength = Vector AttachmentReference -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector AttachmentReference -> Int)
-> Vector AttachmentReference -> Int
forall a b. (a -> b) -> a -> b
$ (Vector AttachmentReference
colorAttachments)
    let pResolveAttachmentsLength :: Int
pResolveAttachmentsLength = Vector AttachmentReference -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector AttachmentReference -> Int)
-> Vector AttachmentReference -> Int
forall a b. (a -> b) -> a -> b
$ (Vector AttachmentReference
resolveAttachments)
    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 (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
pResolveAttachmentsLength Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
pColorAttachmentsLength Bool -> Bool -> Bool
|| Int
pResolveAttachmentsLength Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== 0) (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 "" "pResolveAttachments and pColorAttachments 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
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDescription
p Ptr SubpassDescription -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32)) ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
pColorAttachmentsLength :: Word32))
    Ptr AttachmentReference
pPColorAttachments' <- ((Ptr AttachmentReference -> IO b) -> IO b)
-> ContT b IO (Ptr AttachmentReference)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr AttachmentReference -> IO b) -> IO b)
 -> ContT b IO (Ptr AttachmentReference))
-> ((Ptr AttachmentReference -> IO b) -> IO b)
-> ContT b IO (Ptr AttachmentReference)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr AttachmentReference -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @AttachmentReference ((Vector AttachmentReference -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector AttachmentReference
colorAttachments)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 4
    (Int -> AttachmentReference -> ContT b IO ())
-> Vector AttachmentReference -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: AttachmentReference
e -> ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr AttachmentReference -> AttachmentReference -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr AttachmentReference
pPColorAttachments' Ptr AttachmentReference -> Int -> Ptr AttachmentReference
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr AttachmentReference) (AttachmentReference
e) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())) (Vector AttachmentReference
colorAttachments)
    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 AttachmentReference) -> Ptr AttachmentReference -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDescription
p Ptr SubpassDescription -> Int -> Ptr (Ptr AttachmentReference)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (Ptr AttachmentReference))) (Ptr AttachmentReference
pPColorAttachments')
    Ptr AttachmentReference
pResolveAttachments'' <- if Vector AttachmentReference -> Bool
forall a. Vector a -> Bool
Data.Vector.null (Vector AttachmentReference
resolveAttachments)
      then Ptr AttachmentReference -> ContT b IO (Ptr AttachmentReference)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Ptr AttachmentReference
forall a. Ptr a
nullPtr
      else do
        Ptr AttachmentReference
pPResolveAttachments <- ((Ptr AttachmentReference -> IO b) -> IO b)
-> ContT b IO (Ptr AttachmentReference)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr AttachmentReference -> IO b) -> IO b)
 -> ContT b IO (Ptr AttachmentReference))
-> ((Ptr AttachmentReference -> IO b) -> IO b)
-> ContT b IO (Ptr AttachmentReference)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr AttachmentReference -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @AttachmentReference (((Vector AttachmentReference -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector AttachmentReference
resolveAttachments))) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 4
        (Int -> AttachmentReference -> ContT b IO ())
-> Vector AttachmentReference -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: AttachmentReference
e -> ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr AttachmentReference -> AttachmentReference -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr AttachmentReference
pPResolveAttachments Ptr AttachmentReference -> Int -> Ptr AttachmentReference
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr AttachmentReference) (AttachmentReference
e) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())) ((Vector AttachmentReference
resolveAttachments))
        Ptr AttachmentReference -> ContT b IO (Ptr AttachmentReference)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Ptr AttachmentReference -> ContT b IO (Ptr AttachmentReference))
-> Ptr AttachmentReference -> ContT b IO (Ptr AttachmentReference)
forall a b. (a -> b) -> a -> b
$ Ptr AttachmentReference
pPResolveAttachments
    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 AttachmentReference) -> Ptr AttachmentReference -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDescription
p Ptr SubpassDescription -> Int -> Ptr (Ptr AttachmentReference)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr AttachmentReference))) Ptr AttachmentReference
pResolveAttachments''
    Ptr AttachmentReference
pDepthStencilAttachment'' <- case (Maybe AttachmentReference
depthStencilAttachment) of
      Nothing -> Ptr AttachmentReference -> ContT b IO (Ptr AttachmentReference)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Ptr AttachmentReference
forall a. Ptr a
nullPtr
      Just j :: AttachmentReference
j -> ((Ptr AttachmentReference -> IO b) -> IO b)
-> ContT b IO (Ptr AttachmentReference)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr AttachmentReference -> IO b) -> IO b)
 -> ContT b IO (Ptr AttachmentReference))
-> ((Ptr AttachmentReference -> IO b) -> IO b)
-> ContT b IO (Ptr AttachmentReference)
forall a b. (a -> b) -> a -> b
$ AttachmentReference -> (Ptr AttachmentReference -> IO b) -> IO b
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AttachmentReference
j)
    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 AttachmentReference) -> Ptr AttachmentReference -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDescription
p Ptr SubpassDescription -> Int -> Ptr (Ptr AttachmentReference)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr (Ptr AttachmentReference))) Ptr AttachmentReference
pDepthStencilAttachment''
    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 Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDescription
p Ptr SubpassDescription -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: 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
preserveAttachments)) :: Word32))
    Ptr Word32
pPPreserveAttachments' <- ((Ptr Word32 -> IO b) -> IO b) -> ContT b IO (Ptr Word32)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Word32 -> IO b) -> IO b) -> ContT b IO (Ptr Word32))
-> ((Ptr Word32 -> IO b) -> IO b) -> ContT b IO (Ptr Word32)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr Word32 -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Word32 ((Vector Word32 -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Word32
preserveAttachments)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 4) 4
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> Word32 -> IO ()) -> Vector Word32 -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Word32
e -> Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Word32
pPPreserveAttachments' Ptr Word32 -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32) (Word32
e)) (Vector Word32
preserveAttachments)
    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 Word32) -> Ptr Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDescription
p Ptr SubpassDescription -> Int -> Ptr (Ptr Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr (Ptr Word32))) (Ptr Word32
pPPreserveAttachments')
    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 = 72
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr SubpassDescription -> IO b -> IO b
pokeZeroCStruct p :: Ptr SubpassDescription
p f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PipelineBindPoint -> PipelineBindPoint -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDescription
p Ptr SubpassDescription -> Int -> Ptr PipelineBindPoint
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr PipelineBindPoint)) (PipelineBindPoint
forall a. Zero a => a
zero)
    Ptr AttachmentReference
pPInputAttachments' <- ((Ptr AttachmentReference -> IO b) -> IO b)
-> ContT b IO (Ptr AttachmentReference)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr AttachmentReference -> IO b) -> IO b)
 -> ContT b IO (Ptr AttachmentReference))
-> ((Ptr AttachmentReference -> IO b) -> IO b)
-> ContT b IO (Ptr AttachmentReference)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr AttachmentReference -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @AttachmentReference ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 4
    (Int -> AttachmentReference -> ContT b IO ())
-> Vector AttachmentReference -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: AttachmentReference
e -> ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr AttachmentReference -> AttachmentReference -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr AttachmentReference
pPInputAttachments' Ptr AttachmentReference -> Int -> Ptr AttachmentReference
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr AttachmentReference) (AttachmentReference
e) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())) (Vector AttachmentReference
forall a. Monoid a => a
mempty)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr AttachmentReference) -> Ptr AttachmentReference -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDescription
p Ptr SubpassDescription -> Int -> Ptr (Ptr AttachmentReference)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (Ptr AttachmentReference))) (Ptr AttachmentReference
pPInputAttachments')
    Ptr AttachmentReference
pPColorAttachments' <- ((Ptr AttachmentReference -> IO b) -> IO b)
-> ContT b IO (Ptr AttachmentReference)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr AttachmentReference -> IO b) -> IO b)
 -> ContT b IO (Ptr AttachmentReference))
-> ((Ptr AttachmentReference -> IO b) -> IO b)
-> ContT b IO (Ptr AttachmentReference)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr AttachmentReference -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @AttachmentReference ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 4
    (Int -> AttachmentReference -> ContT b IO ())
-> Vector AttachmentReference -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: AttachmentReference
e -> ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr AttachmentReference -> AttachmentReference -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr AttachmentReference
pPColorAttachments' Ptr AttachmentReference -> Int -> Ptr AttachmentReference
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr AttachmentReference) (AttachmentReference
e) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())) (Vector AttachmentReference
forall a. Monoid a => a
mempty)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr AttachmentReference) -> Ptr AttachmentReference -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDescription
p Ptr SubpassDescription -> Int -> Ptr (Ptr AttachmentReference)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (Ptr AttachmentReference))) (Ptr AttachmentReference
pPColorAttachments')
    Ptr Word32
pPPreserveAttachments' <- ((Ptr Word32 -> IO b) -> IO b) -> ContT b IO (Ptr Word32)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Word32 -> IO b) -> IO b) -> ContT b IO (Ptr Word32))
-> ((Ptr Word32 -> IO b) -> IO b) -> ContT b IO (Ptr Word32)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr Word32 -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Word32 ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 4) 4
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> Word32 -> IO ()) -> Vector Word32 -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Word32
e -> Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Word32
pPPreserveAttachments' Ptr Word32 -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32) (Word32
e)) (Vector Word32
forall a. Monoid a => a
mempty)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr Word32) -> Ptr Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDescription
p Ptr SubpassDescription -> Int -> Ptr (Ptr Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr (Ptr Word32))) (Ptr Word32
pPPreserveAttachments')
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
instance FromCStruct SubpassDescription where
  peekCStruct :: Ptr SubpassDescription -> IO SubpassDescription
peekCStruct p :: Ptr SubpassDescription
p = do
    SubpassDescriptionFlags
flags <- Ptr SubpassDescriptionFlags -> IO SubpassDescriptionFlags
forall a. Storable a => Ptr a -> IO a
peek @SubpassDescriptionFlags ((Ptr SubpassDescription
p Ptr SubpassDescription -> Int -> Ptr SubpassDescriptionFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr SubpassDescriptionFlags))
    PipelineBindPoint
pipelineBindPoint <- Ptr PipelineBindPoint -> IO PipelineBindPoint
forall a. Storable a => Ptr a -> IO a
peek @PipelineBindPoint ((Ptr SubpassDescription
p Ptr SubpassDescription -> Int -> Ptr PipelineBindPoint
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr PipelineBindPoint))
    Word32
inputAttachmentCount <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr SubpassDescription
p Ptr SubpassDescription -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32))
    Ptr AttachmentReference
pInputAttachments <- Ptr (Ptr AttachmentReference) -> IO (Ptr AttachmentReference)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr AttachmentReference) ((Ptr SubpassDescription
p Ptr SubpassDescription -> Int -> Ptr (Ptr AttachmentReference)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (Ptr AttachmentReference)))
    Vector AttachmentReference
pInputAttachments' <- Int
-> (Int -> IO AttachmentReference)
-> IO (Vector AttachmentReference)
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
inputAttachmentCount) (\i :: Int
i -> Ptr AttachmentReference -> IO AttachmentReference
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @AttachmentReference ((Ptr AttachmentReference
pInputAttachments Ptr AttachmentReference -> Int -> Ptr AttachmentReference
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr AttachmentReference)))
    Word32
colorAttachmentCount <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr SubpassDescription
p Ptr SubpassDescription -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32))
    Ptr AttachmentReference
pColorAttachments <- Ptr (Ptr AttachmentReference) -> IO (Ptr AttachmentReference)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr AttachmentReference) ((Ptr SubpassDescription
p Ptr SubpassDescription -> Int -> Ptr (Ptr AttachmentReference)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (Ptr AttachmentReference)))
    Vector AttachmentReference
pColorAttachments' <- Int
-> (Int -> IO AttachmentReference)
-> IO (Vector AttachmentReference)
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
colorAttachmentCount) (\i :: Int
i -> Ptr AttachmentReference -> IO AttachmentReference
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @AttachmentReference ((Ptr AttachmentReference
pColorAttachments Ptr AttachmentReference -> Int -> Ptr AttachmentReference
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr AttachmentReference)))
    Ptr AttachmentReference
pResolveAttachments <- Ptr (Ptr AttachmentReference) -> IO (Ptr AttachmentReference)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr AttachmentReference) ((Ptr SubpassDescription
p Ptr SubpassDescription -> Int -> Ptr (Ptr AttachmentReference)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr AttachmentReference)))
    let pResolveAttachmentsLength :: Int
pResolveAttachmentsLength = if Ptr AttachmentReference
pResolveAttachments Ptr AttachmentReference -> Ptr AttachmentReference -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr AttachmentReference
forall a. Ptr a
nullPtr then 0 else (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
colorAttachmentCount)
    Vector AttachmentReference
pResolveAttachments' <- Int
-> (Int -> IO AttachmentReference)
-> IO (Vector AttachmentReference)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM Int
pResolveAttachmentsLength (\i :: Int
i -> Ptr AttachmentReference -> IO AttachmentReference
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @AttachmentReference ((Ptr AttachmentReference
pResolveAttachments Ptr AttachmentReference -> Int -> Ptr AttachmentReference
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr AttachmentReference)))
    Ptr AttachmentReference
pDepthStencilAttachment <- Ptr (Ptr AttachmentReference) -> IO (Ptr AttachmentReference)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr AttachmentReference) ((Ptr SubpassDescription
p Ptr SubpassDescription -> Int -> Ptr (Ptr AttachmentReference)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr (Ptr AttachmentReference)))
    Maybe AttachmentReference
pDepthStencilAttachment' <- (Ptr AttachmentReference -> IO AttachmentReference)
-> Ptr AttachmentReference -> IO (Maybe AttachmentReference)
forall a b. (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
maybePeek (\j :: Ptr AttachmentReference
j -> Ptr AttachmentReference -> IO AttachmentReference
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @AttachmentReference (Ptr AttachmentReference
j)) Ptr AttachmentReference
pDepthStencilAttachment
    Word32
preserveAttachmentCount <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr SubpassDescription
p Ptr SubpassDescription -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr Word32))
    Ptr Word32
pPreserveAttachments <- Ptr (Ptr Word32) -> IO (Ptr Word32)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr Word32) ((Ptr SubpassDescription
p Ptr SubpassDescription -> Int -> Ptr (Ptr Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr (Ptr Word32)))
    Vector Word32
pPreserveAttachments' <- 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
preserveAttachmentCount) (\i :: Int
i -> Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr Word32
pPreserveAttachments Ptr Word32 -> Int -> Ptr Word32
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32)))
    SubpassDescription -> IO SubpassDescription
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SubpassDescription -> IO SubpassDescription)
-> SubpassDescription -> IO SubpassDescription
forall a b. (a -> b) -> a -> b
$ SubpassDescriptionFlags
-> PipelineBindPoint
-> Vector AttachmentReference
-> Vector AttachmentReference
-> Vector AttachmentReference
-> Maybe AttachmentReference
-> Vector Word32
-> SubpassDescription
SubpassDescription
             SubpassDescriptionFlags
flags PipelineBindPoint
pipelineBindPoint Vector AttachmentReference
pInputAttachments' Vector AttachmentReference
pColorAttachments' Vector AttachmentReference
pResolveAttachments' Maybe AttachmentReference
pDepthStencilAttachment' Vector Word32
pPreserveAttachments'
instance Zero SubpassDescription where
  zero :: SubpassDescription
zero = SubpassDescriptionFlags
-> PipelineBindPoint
-> Vector AttachmentReference
-> Vector AttachmentReference
-> Vector AttachmentReference
-> Maybe AttachmentReference
-> Vector Word32
-> SubpassDescription
SubpassDescription
           SubpassDescriptionFlags
forall a. Zero a => a
zero
           PipelineBindPoint
forall a. Zero a => a
zero
           Vector AttachmentReference
forall a. Monoid a => a
mempty
           Vector AttachmentReference
forall a. Monoid a => a
mempty
           Vector AttachmentReference
forall a. Monoid a => a
mempty
           Maybe AttachmentReference
forall a. Maybe a
Nothing
           Vector Word32
forall a. Monoid a => a
mempty
data SubpassDependency = SubpassDependency
  { 
    
    SubpassDependency -> Word32
srcSubpass :: Word32
  , 
    
    SubpassDependency -> Word32
dstSubpass :: Word32
  , 
    
    
    
    SubpassDependency -> PipelineStageFlags
srcStageMask :: PipelineStageFlags
  , 
    
    
    
    SubpassDependency -> PipelineStageFlags
dstStageMask :: PipelineStageFlags
  , 
    
    
    SubpassDependency -> AccessFlags
srcAccessMask :: AccessFlags
  , 
    
    
    SubpassDependency -> AccessFlags
dstAccessMask :: AccessFlags
  , 
    
    SubpassDependency -> DependencyFlags
dependencyFlags :: DependencyFlags
  }
  deriving (Typeable)
deriving instance Show SubpassDependency
instance ToCStruct SubpassDependency where
  withCStruct :: SubpassDependency -> (Ptr SubpassDependency -> IO b) -> IO b
withCStruct x :: SubpassDependency
x f :: Ptr SubpassDependency -> IO b
f = Int -> Int -> (Ptr SubpassDependency -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 28 4 ((Ptr SubpassDependency -> IO b) -> IO b)
-> (Ptr SubpassDependency -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr SubpassDependency
p -> Ptr SubpassDependency -> SubpassDependency -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr SubpassDependency
p SubpassDependency
x (Ptr SubpassDependency -> IO b
f Ptr SubpassDependency
p)
  pokeCStruct :: Ptr SubpassDependency -> SubpassDependency -> IO b -> IO b
pokeCStruct p :: Ptr SubpassDependency
p SubpassDependency{..} f :: IO b
f = do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDependency
p Ptr SubpassDependency -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32)) (Word32
srcSubpass)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDependency
p Ptr SubpassDependency -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) (Word32
dstSubpass)
    Ptr PipelineStageFlags -> PipelineStageFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDependency
p Ptr SubpassDependency -> Int -> Ptr PipelineStageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr PipelineStageFlags)) (PipelineStageFlags
srcStageMask)
    Ptr PipelineStageFlags -> PipelineStageFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDependency
p Ptr SubpassDependency -> Int -> Ptr PipelineStageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr PipelineStageFlags)) (PipelineStageFlags
dstStageMask)
    Ptr AccessFlags -> AccessFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDependency
p Ptr SubpassDependency -> Int -> Ptr AccessFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr AccessFlags)) (AccessFlags
srcAccessMask)
    Ptr AccessFlags -> AccessFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDependency
p Ptr SubpassDependency -> Int -> Ptr AccessFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr AccessFlags)) (AccessFlags
dstAccessMask)
    Ptr DependencyFlags -> DependencyFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDependency
p Ptr SubpassDependency -> Int -> Ptr DependencyFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DependencyFlags)) (DependencyFlags
dependencyFlags)
    IO b
f
  cStructSize :: Int
cStructSize = 28
  cStructAlignment :: Int
cStructAlignment = 4
  pokeZeroCStruct :: Ptr SubpassDependency -> IO b -> IO b
pokeZeroCStruct p :: Ptr SubpassDependency
p f :: IO b
f = do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDependency
p Ptr SubpassDependency -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDependency
p Ptr SubpassDependency -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr PipelineStageFlags -> PipelineStageFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDependency
p Ptr SubpassDependency -> Int -> Ptr PipelineStageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr PipelineStageFlags)) (PipelineStageFlags
forall a. Zero a => a
zero)
    Ptr PipelineStageFlags -> PipelineStageFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDependency
p Ptr SubpassDependency -> Int -> Ptr PipelineStageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr PipelineStageFlags)) (PipelineStageFlags
forall a. Zero a => a
zero)
    IO b
f
instance FromCStruct SubpassDependency where
  peekCStruct :: Ptr SubpassDependency -> IO SubpassDependency
peekCStruct p :: Ptr SubpassDependency
p = do
    Word32
srcSubpass <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr SubpassDependency
p Ptr SubpassDependency -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32))
    Word32
dstSubpass <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr SubpassDependency
p Ptr SubpassDependency -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32))
    PipelineStageFlags
srcStageMask <- Ptr PipelineStageFlags -> IO PipelineStageFlags
forall a. Storable a => Ptr a -> IO a
peek @PipelineStageFlags ((Ptr SubpassDependency
p Ptr SubpassDependency -> Int -> Ptr PipelineStageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr PipelineStageFlags))
    PipelineStageFlags
dstStageMask <- Ptr PipelineStageFlags -> IO PipelineStageFlags
forall a. Storable a => Ptr a -> IO a
peek @PipelineStageFlags ((Ptr SubpassDependency
p Ptr SubpassDependency -> Int -> Ptr PipelineStageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr PipelineStageFlags))
    AccessFlags
srcAccessMask <- Ptr AccessFlags -> IO AccessFlags
forall a. Storable a => Ptr a -> IO a
peek @AccessFlags ((Ptr SubpassDependency
p Ptr SubpassDependency -> Int -> Ptr AccessFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr AccessFlags))
    AccessFlags
dstAccessMask <- Ptr AccessFlags -> IO AccessFlags
forall a. Storable a => Ptr a -> IO a
peek @AccessFlags ((Ptr SubpassDependency
p Ptr SubpassDependency -> Int -> Ptr AccessFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr AccessFlags))
    DependencyFlags
dependencyFlags <- Ptr DependencyFlags -> IO DependencyFlags
forall a. Storable a => Ptr a -> IO a
peek @DependencyFlags ((Ptr SubpassDependency
p Ptr SubpassDependency -> Int -> Ptr DependencyFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DependencyFlags))
    SubpassDependency -> IO SubpassDependency
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SubpassDependency -> IO SubpassDependency)
-> SubpassDependency -> IO SubpassDependency
forall a b. (a -> b) -> a -> b
$ Word32
-> Word32
-> PipelineStageFlags
-> PipelineStageFlags
-> AccessFlags
-> AccessFlags
-> DependencyFlags
-> SubpassDependency
SubpassDependency
             Word32
srcSubpass Word32
dstSubpass PipelineStageFlags
srcStageMask PipelineStageFlags
dstStageMask AccessFlags
srcAccessMask AccessFlags
dstAccessMask DependencyFlags
dependencyFlags
instance Storable SubpassDependency where
  sizeOf :: SubpassDependency -> Int
sizeOf ~SubpassDependency
_ = 28
  alignment :: SubpassDependency -> Int
alignment ~SubpassDependency
_ = 4
  peek :: Ptr SubpassDependency -> IO SubpassDependency
peek = Ptr SubpassDependency -> IO SubpassDependency
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr SubpassDependency -> SubpassDependency -> IO ()
poke ptr :: Ptr SubpassDependency
ptr poked :: SubpassDependency
poked = Ptr SubpassDependency -> SubpassDependency -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr SubpassDependency
ptr SubpassDependency
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero SubpassDependency where
  zero :: SubpassDependency
zero = Word32
-> Word32
-> PipelineStageFlags
-> PipelineStageFlags
-> AccessFlags
-> AccessFlags
-> DependencyFlags
-> SubpassDependency
SubpassDependency
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           PipelineStageFlags
forall a. Zero a => a
zero
           PipelineStageFlags
forall a. Zero a => a
zero
           AccessFlags
forall a. Zero a => a
zero
           AccessFlags
forall a. Zero a => a
zero
           DependencyFlags
forall a. Zero a => a
zero
data RenderPassCreateInfo (es :: [Type]) = RenderPassCreateInfo
  { 
    RenderPassCreateInfo es -> Chain es
next :: Chain es
  , 
    
    RenderPassCreateInfo es -> RenderPassCreateFlags
flags :: RenderPassCreateFlags
  , 
    
    
    RenderPassCreateInfo es -> Vector AttachmentDescription
attachments :: Vector AttachmentDescription
  , 
    
    RenderPassCreateInfo es -> Vector SubpassDescription
subpasses :: Vector SubpassDescription
  , 
    
    
    RenderPassCreateInfo es -> Vector SubpassDependency
dependencies :: Vector SubpassDependency
  }
  deriving (Typeable)
deriving instance Show (Chain es) => Show (RenderPassCreateInfo es)
instance Extensible RenderPassCreateInfo where
  extensibleType :: StructureType
extensibleType = StructureType
STRUCTURE_TYPE_RENDER_PASS_CREATE_INFO
  setNext :: RenderPassCreateInfo ds -> Chain es -> RenderPassCreateInfo es
setNext x :: RenderPassCreateInfo ds
x next :: Chain es
next = RenderPassCreateInfo ds
x{$sel:next:RenderPassCreateInfo :: Chain es
next = Chain es
next}
  getNext :: RenderPassCreateInfo es -> Chain es
getNext RenderPassCreateInfo{..} = Chain es
next
  extends :: forall e b proxy. Typeable e => proxy e -> (Extends RenderPassCreateInfo e => b) -> Maybe b
  extends :: proxy e -> (Extends RenderPassCreateInfo e => b) -> Maybe b
extends _ f :: Extends RenderPassCreateInfo e => b
f
    | Just Refl <- (Typeable e, Typeable RenderPassFragmentDensityMapCreateInfoEXT) =>
Maybe (e :~: RenderPassFragmentDensityMapCreateInfoEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @RenderPassFragmentDensityMapCreateInfoEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends RenderPassCreateInfo e => b
f
    | Just Refl <- (Typeable e, Typeable RenderPassInputAttachmentAspectCreateInfo) =>
Maybe (e :~: RenderPassInputAttachmentAspectCreateInfo)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @RenderPassInputAttachmentAspectCreateInfo = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends RenderPassCreateInfo e => b
f
    | Just Refl <- (Typeable e, Typeable RenderPassMultiviewCreateInfo) =>
Maybe (e :~: RenderPassMultiviewCreateInfo)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @RenderPassMultiviewCreateInfo = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends RenderPassCreateInfo e => b
f
    | Bool
otherwise = Maybe b
forall a. Maybe a
Nothing
instance (Extendss RenderPassCreateInfo es, PokeChain es) => ToCStruct (RenderPassCreateInfo es) where
  withCStruct :: RenderPassCreateInfo es
-> (Ptr (RenderPassCreateInfo es) -> IO b) -> IO b
withCStruct x :: RenderPassCreateInfo es
x f :: Ptr (RenderPassCreateInfo es) -> IO b
f = Int -> Int -> (Ptr (RenderPassCreateInfo es) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 64 8 ((Ptr (RenderPassCreateInfo es) -> IO b) -> IO b)
-> (Ptr (RenderPassCreateInfo es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr (RenderPassCreateInfo es)
p -> Ptr (RenderPassCreateInfo es)
-> RenderPassCreateInfo es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (RenderPassCreateInfo es)
p RenderPassCreateInfo es
x (Ptr (RenderPassCreateInfo es) -> IO b
f Ptr (RenderPassCreateInfo es)
p)
  pokeCStruct :: Ptr (RenderPassCreateInfo es)
-> RenderPassCreateInfo es -> IO b -> IO b
pokeCStruct p :: Ptr (RenderPassCreateInfo es)
p RenderPassCreateInfo{..} f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RenderPassCreateInfo es)
p Ptr (RenderPassCreateInfo es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_RENDER_PASS_CREATE_INFO)
    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 (RenderPassCreateInfo es)
p Ptr (RenderPassCreateInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext''
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr RenderPassCreateFlags -> RenderPassCreateFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RenderPassCreateInfo es)
p Ptr (RenderPassCreateInfo es) -> Int -> Ptr RenderPassCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr RenderPassCreateFlags)) (RenderPassCreateFlags
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 Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RenderPassCreateInfo es)
p Ptr (RenderPassCreateInfo es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector AttachmentDescription -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector AttachmentDescription -> Int)
-> Vector AttachmentDescription -> Int
forall a b. (a -> b) -> a -> b
$ (Vector AttachmentDescription
attachments)) :: Word32))
    Ptr AttachmentDescription
pPAttachments' <- ((Ptr AttachmentDescription -> IO b) -> IO b)
-> ContT b IO (Ptr AttachmentDescription)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr AttachmentDescription -> IO b) -> IO b)
 -> ContT b IO (Ptr AttachmentDescription))
-> ((Ptr AttachmentDescription -> IO b) -> IO b)
-> ContT b IO (Ptr AttachmentDescription)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr AttachmentDescription -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @AttachmentDescription ((Vector AttachmentDescription -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector AttachmentDescription
attachments)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 36) 4
    (Int -> AttachmentDescription -> ContT b IO ())
-> Vector AttachmentDescription -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: AttachmentDescription
e -> ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr AttachmentDescription -> AttachmentDescription -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr AttachmentDescription
pPAttachments' Ptr AttachmentDescription -> Int -> Ptr AttachmentDescription
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (36 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr AttachmentDescription) (AttachmentDescription
e) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())) (Vector AttachmentDescription
attachments)
    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 AttachmentDescription)
-> Ptr AttachmentDescription -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RenderPassCreateInfo es)
p Ptr (RenderPassCreateInfo es)
-> Int -> Ptr (Ptr AttachmentDescription)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr AttachmentDescription))) (Ptr AttachmentDescription
pPAttachments')
    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 Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RenderPassCreateInfo es)
p Ptr (RenderPassCreateInfo es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word32)) ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector SubpassDescription -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector SubpassDescription -> Int)
-> Vector SubpassDescription -> Int
forall a b. (a -> b) -> a -> b
$ (Vector SubpassDescription
subpasses)) :: Word32))
    Ptr SubpassDescription
pPSubpasses' <- ((Ptr SubpassDescription -> IO b) -> IO b)
-> ContT b IO (Ptr SubpassDescription)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr SubpassDescription -> IO b) -> IO b)
 -> ContT b IO (Ptr SubpassDescription))
-> ((Ptr SubpassDescription -> IO b) -> IO b)
-> ContT b IO (Ptr SubpassDescription)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr SubpassDescription -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @SubpassDescription ((Vector SubpassDescription -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector SubpassDescription
subpasses)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 72) 8
    (Int -> SubpassDescription -> ContT b IO ())
-> Vector SubpassDescription -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SubpassDescription
e -> ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr SubpassDescription -> SubpassDescription -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr SubpassDescription
pPSubpasses' Ptr SubpassDescription -> Int -> Ptr SubpassDescription
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (72 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SubpassDescription) (SubpassDescription
e) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())) (Vector SubpassDescription
subpasses)
    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 SubpassDescription) -> Ptr SubpassDescription -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RenderPassCreateInfo es)
p Ptr (RenderPassCreateInfo es)
-> Int -> Ptr (Ptr SubpassDescription)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr SubpassDescription))) (Ptr SubpassDescription
pPSubpasses')
    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 Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RenderPassCreateInfo es)
p Ptr (RenderPassCreateInfo es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Word32)) ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector SubpassDependency -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector SubpassDependency -> Int)
-> Vector SubpassDependency -> Int
forall a b. (a -> b) -> a -> b
$ (Vector SubpassDependency
dependencies)) :: Word32))
    Ptr SubpassDependency
pPDependencies' <- ((Ptr SubpassDependency -> IO b) -> IO b)
-> ContT b IO (Ptr SubpassDependency)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr SubpassDependency -> IO b) -> IO b)
 -> ContT b IO (Ptr SubpassDependency))
-> ((Ptr SubpassDependency -> IO b) -> IO b)
-> ContT b IO (Ptr SubpassDependency)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr SubpassDependency -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @SubpassDependency ((Vector SubpassDependency -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector SubpassDependency
dependencies)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 28) 4
    (Int -> SubpassDependency -> ContT b IO ())
-> Vector SubpassDependency -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SubpassDependency
e -> ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr SubpassDependency -> SubpassDependency -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr SubpassDependency
pPDependencies' Ptr SubpassDependency -> Int -> Ptr SubpassDependency
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (28 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SubpassDependency) (SubpassDependency
e) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())) (Vector SubpassDependency
dependencies)
    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 SubpassDependency) -> Ptr SubpassDependency -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RenderPassCreateInfo es)
p Ptr (RenderPassCreateInfo es) -> Int -> Ptr (Ptr SubpassDependency)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr (Ptr SubpassDependency))) (Ptr SubpassDependency
pPDependencies')
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = 64
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr (RenderPassCreateInfo es) -> IO b -> IO b
pokeZeroCStruct p :: Ptr (RenderPassCreateInfo es)
p f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RenderPassCreateInfo es)
p Ptr (RenderPassCreateInfo es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_RENDER_PASS_CREATE_INFO)
    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 (RenderPassCreateInfo es)
p Ptr (RenderPassCreateInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext'
    Ptr AttachmentDescription
pPAttachments' <- ((Ptr AttachmentDescription -> IO b) -> IO b)
-> ContT b IO (Ptr AttachmentDescription)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr AttachmentDescription -> IO b) -> IO b)
 -> ContT b IO (Ptr AttachmentDescription))
-> ((Ptr AttachmentDescription -> IO b) -> IO b)
-> ContT b IO (Ptr AttachmentDescription)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr AttachmentDescription -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @AttachmentDescription ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 36) 4
    (Int -> AttachmentDescription -> ContT b IO ())
-> Vector AttachmentDescription -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: AttachmentDescription
e -> ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr AttachmentDescription -> AttachmentDescription -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr AttachmentDescription
pPAttachments' Ptr AttachmentDescription -> Int -> Ptr AttachmentDescription
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (36 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr AttachmentDescription) (AttachmentDescription
e) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())) (Vector AttachmentDescription
forall a. Monoid a => a
mempty)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr AttachmentDescription)
-> Ptr AttachmentDescription -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RenderPassCreateInfo es)
p Ptr (RenderPassCreateInfo es)
-> Int -> Ptr (Ptr AttachmentDescription)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr AttachmentDescription))) (Ptr AttachmentDescription
pPAttachments')
    Ptr SubpassDescription
pPSubpasses' <- ((Ptr SubpassDescription -> IO b) -> IO b)
-> ContT b IO (Ptr SubpassDescription)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr SubpassDescription -> IO b) -> IO b)
 -> ContT b IO (Ptr SubpassDescription))
-> ((Ptr SubpassDescription -> IO b) -> IO b)
-> ContT b IO (Ptr SubpassDescription)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr SubpassDescription -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @SubpassDescription ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 72) 8
    (Int -> SubpassDescription -> ContT b IO ())
-> Vector SubpassDescription -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SubpassDescription
e -> ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr SubpassDescription -> SubpassDescription -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr SubpassDescription
pPSubpasses' Ptr SubpassDescription -> Int -> Ptr SubpassDescription
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (72 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SubpassDescription) (SubpassDescription
e) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())) (Vector SubpassDescription
forall a. Monoid a => a
mempty)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr SubpassDescription) -> Ptr SubpassDescription -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RenderPassCreateInfo es)
p Ptr (RenderPassCreateInfo es)
-> Int -> Ptr (Ptr SubpassDescription)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr SubpassDescription))) (Ptr SubpassDescription
pPSubpasses')
    Ptr SubpassDependency
pPDependencies' <- ((Ptr SubpassDependency -> IO b) -> IO b)
-> ContT b IO (Ptr SubpassDependency)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr SubpassDependency -> IO b) -> IO b)
 -> ContT b IO (Ptr SubpassDependency))
-> ((Ptr SubpassDependency -> IO b) -> IO b)
-> ContT b IO (Ptr SubpassDependency)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr SubpassDependency -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @SubpassDependency ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 28) 4
    (Int -> SubpassDependency -> ContT b IO ())
-> Vector SubpassDependency -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SubpassDependency
e -> ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr SubpassDependency -> SubpassDependency -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr SubpassDependency
pPDependencies' Ptr SubpassDependency -> Int -> Ptr SubpassDependency
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (28 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SubpassDependency) (SubpassDependency
e) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())) (Vector SubpassDependency
forall a. Monoid a => a
mempty)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr SubpassDependency) -> Ptr SubpassDependency -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RenderPassCreateInfo es)
p Ptr (RenderPassCreateInfo es) -> Int -> Ptr (Ptr SubpassDependency)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr (Ptr SubpassDependency))) (Ptr SubpassDependency
pPDependencies')
    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 RenderPassCreateInfo es, PeekChain es) => FromCStruct (RenderPassCreateInfo es) where
  peekCStruct :: Ptr (RenderPassCreateInfo es) -> IO (RenderPassCreateInfo es)
peekCStruct p :: Ptr (RenderPassCreateInfo es)
p = do
    Ptr ()
pNext <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (RenderPassCreateInfo es)
p Ptr (RenderPassCreateInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ())))
    Chain es
next <- Ptr (Chain es) -> IO (Chain es)
forall (es :: [*]). PeekChain es => Ptr (Chain es) -> IO (Chain es)
peekChain (Ptr () -> Ptr (Chain es)
forall a b. Ptr a -> Ptr b
castPtr Ptr ()
pNext)
    RenderPassCreateFlags
flags <- Ptr RenderPassCreateFlags -> IO RenderPassCreateFlags
forall a. Storable a => Ptr a -> IO a
peek @RenderPassCreateFlags ((Ptr (RenderPassCreateInfo es)
p Ptr (RenderPassCreateInfo es) -> Int -> Ptr RenderPassCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr RenderPassCreateFlags))
    Word32
attachmentCount <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (RenderPassCreateInfo es)
p Ptr (RenderPassCreateInfo es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32))
    Ptr AttachmentDescription
pAttachments <- Ptr (Ptr AttachmentDescription) -> IO (Ptr AttachmentDescription)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr AttachmentDescription) ((Ptr (RenderPassCreateInfo es)
p Ptr (RenderPassCreateInfo es)
-> Int -> Ptr (Ptr AttachmentDescription)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr AttachmentDescription)))
    Vector AttachmentDescription
pAttachments' <- Int
-> (Int -> IO AttachmentDescription)
-> IO (Vector AttachmentDescription)
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
attachmentCount) (\i :: Int
i -> Ptr AttachmentDescription -> IO AttachmentDescription
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @AttachmentDescription ((Ptr AttachmentDescription
pAttachments Ptr AttachmentDescription -> Int -> Ptr AttachmentDescription
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (36 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr AttachmentDescription)))
    Word32
subpassCount <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (RenderPassCreateInfo es)
p Ptr (RenderPassCreateInfo es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word32))
    Ptr SubpassDescription
pSubpasses <- Ptr (Ptr SubpassDescription) -> IO (Ptr SubpassDescription)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr SubpassDescription) ((Ptr (RenderPassCreateInfo es)
p Ptr (RenderPassCreateInfo es)
-> Int -> Ptr (Ptr SubpassDescription)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr SubpassDescription)))
    Vector SubpassDescription
pSubpasses' <- Int
-> (Int -> IO SubpassDescription) -> IO (Vector SubpassDescription)
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
subpassCount) (\i :: Int
i -> Ptr SubpassDescription -> IO SubpassDescription
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @SubpassDescription ((Ptr SubpassDescription
pSubpasses Ptr SubpassDescription -> Int -> Ptr SubpassDescription
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (72 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SubpassDescription)))
    Word32
dependencyCount <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (RenderPassCreateInfo es)
p Ptr (RenderPassCreateInfo es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Word32))
    Ptr SubpassDependency
pDependencies <- Ptr (Ptr SubpassDependency) -> IO (Ptr SubpassDependency)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr SubpassDependency) ((Ptr (RenderPassCreateInfo es)
p Ptr (RenderPassCreateInfo es) -> Int -> Ptr (Ptr SubpassDependency)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr (Ptr SubpassDependency)))
    Vector SubpassDependency
pDependencies' <- Int
-> (Int -> IO SubpassDependency) -> IO (Vector SubpassDependency)
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
dependencyCount) (\i :: Int
i -> Ptr SubpassDependency -> IO SubpassDependency
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @SubpassDependency ((Ptr SubpassDependency
pDependencies Ptr SubpassDependency -> Int -> Ptr SubpassDependency
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (28 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SubpassDependency)))
    RenderPassCreateInfo es -> IO (RenderPassCreateInfo es)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (RenderPassCreateInfo es -> IO (RenderPassCreateInfo es))
-> RenderPassCreateInfo es -> IO (RenderPassCreateInfo es)
forall a b. (a -> b) -> a -> b
$ Chain es
-> RenderPassCreateFlags
-> Vector AttachmentDescription
-> Vector SubpassDescription
-> Vector SubpassDependency
-> RenderPassCreateInfo es
forall (es :: [*]).
Chain es
-> RenderPassCreateFlags
-> Vector AttachmentDescription
-> Vector SubpassDescription
-> Vector SubpassDependency
-> RenderPassCreateInfo es
RenderPassCreateInfo
             Chain es
next RenderPassCreateFlags
flags Vector AttachmentDescription
pAttachments' Vector SubpassDescription
pSubpasses' Vector SubpassDependency
pDependencies'
instance es ~ '[] => Zero (RenderPassCreateInfo es) where
  zero :: RenderPassCreateInfo es
zero = Chain es
-> RenderPassCreateFlags
-> Vector AttachmentDescription
-> Vector SubpassDescription
-> Vector SubpassDependency
-> RenderPassCreateInfo es
forall (es :: [*]).
Chain es
-> RenderPassCreateFlags
-> Vector AttachmentDescription
-> Vector SubpassDescription
-> Vector SubpassDependency
-> RenderPassCreateInfo es
RenderPassCreateInfo
           ()
           RenderPassCreateFlags
forall a. Zero a => a
zero
           Vector AttachmentDescription
forall a. Monoid a => a
mempty
           Vector SubpassDescription
forall a. Monoid a => a
mempty
           Vector SubpassDependency
forall a. Monoid a => a
mempty
data FramebufferCreateInfo (es :: [Type]) = FramebufferCreateInfo
  { 
    FramebufferCreateInfo es -> Chain es
next :: Chain es
  , 
    
    FramebufferCreateInfo es -> FramebufferCreateFlags
flags :: FramebufferCreateFlags
  , 
    
    
    
    FramebufferCreateInfo es -> RenderPass
renderPass :: RenderPass
  , 
    
    
    
    
    
    FramebufferCreateInfo es -> Vector ImageView
attachments :: Vector ImageView
  , 
    
    
    
    FramebufferCreateInfo es -> Word32
width :: Word32
  , 
    FramebufferCreateInfo es -> Word32
height :: Word32
  , 
    FramebufferCreateInfo es -> Word32
layers :: Word32
  }
  deriving (Typeable)
deriving instance Show (Chain es) => Show (FramebufferCreateInfo es)
instance Extensible FramebufferCreateInfo where
  extensibleType :: StructureType
extensibleType = StructureType
STRUCTURE_TYPE_FRAMEBUFFER_CREATE_INFO
  setNext :: FramebufferCreateInfo ds -> Chain es -> FramebufferCreateInfo es
setNext x :: FramebufferCreateInfo ds
x next :: Chain es
next = FramebufferCreateInfo ds
x{$sel:next:FramebufferCreateInfo :: Chain es
next = Chain es
next}
  getNext :: FramebufferCreateInfo es -> Chain es
getNext FramebufferCreateInfo{..} = Chain es
next
  extends :: forall e b proxy. Typeable e => proxy e -> (Extends FramebufferCreateInfo e => b) -> Maybe b
  extends :: proxy e -> (Extends FramebufferCreateInfo e => b) -> Maybe b
extends _ f :: Extends FramebufferCreateInfo e => b
f
    | Just Refl <- (Typeable e, Typeable FramebufferAttachmentsCreateInfo) =>
Maybe (e :~: FramebufferAttachmentsCreateInfo)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @FramebufferAttachmentsCreateInfo = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends FramebufferCreateInfo e => b
f
    | Bool
otherwise = Maybe b
forall a. Maybe a
Nothing
instance (Extendss FramebufferCreateInfo es, PokeChain es) => ToCStruct (FramebufferCreateInfo es) where
  withCStruct :: FramebufferCreateInfo es
-> (Ptr (FramebufferCreateInfo es) -> IO b) -> IO b
withCStruct x :: FramebufferCreateInfo es
x f :: Ptr (FramebufferCreateInfo es) -> IO b
f = Int -> Int -> (Ptr (FramebufferCreateInfo es) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 64 8 ((Ptr (FramebufferCreateInfo es) -> IO b) -> IO b)
-> (Ptr (FramebufferCreateInfo es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr (FramebufferCreateInfo es)
p -> Ptr (FramebufferCreateInfo es)
-> FramebufferCreateInfo es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (FramebufferCreateInfo es)
p FramebufferCreateInfo es
x (Ptr (FramebufferCreateInfo es) -> IO b
f Ptr (FramebufferCreateInfo es)
p)
  pokeCStruct :: Ptr (FramebufferCreateInfo es)
-> FramebufferCreateInfo es -> IO b -> IO b
pokeCStruct p :: Ptr (FramebufferCreateInfo es)
p FramebufferCreateInfo{..} f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (FramebufferCreateInfo es)
p Ptr (FramebufferCreateInfo es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_FRAMEBUFFER_CREATE_INFO)
    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 (FramebufferCreateInfo es)
p Ptr (FramebufferCreateInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext''
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr FramebufferCreateFlags -> FramebufferCreateFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (FramebufferCreateInfo es)
p Ptr (FramebufferCreateInfo es) -> Int -> Ptr FramebufferCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr FramebufferCreateFlags)) (FramebufferCreateFlags
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
$ ("pRenderPass" ::: Ptr RenderPass) -> RenderPass -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (FramebufferCreateInfo es)
p Ptr (FramebufferCreateInfo es)
-> Int -> "pRenderPass" ::: Ptr RenderPass
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr RenderPass)) (RenderPass
renderPass)
    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 Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (FramebufferCreateInfo es)
p Ptr (FramebufferCreateInfo es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word32)) ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector ImageView -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector ImageView -> Int) -> Vector ImageView -> Int
forall a b. (a -> b) -> a -> b
$ (Vector ImageView
attachments)) :: Word32))
    Ptr ImageView
pPAttachments' <- ((Ptr ImageView -> IO b) -> IO b) -> ContT b IO (Ptr ImageView)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr ImageView -> IO b) -> IO b) -> ContT b IO (Ptr ImageView))
-> ((Ptr ImageView -> IO b) -> IO b) -> ContT b IO (Ptr ImageView)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr ImageView -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @ImageView ((Vector ImageView -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector ImageView
attachments)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 8
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> ImageView -> IO ()) -> Vector ImageView -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: ImageView
e -> Ptr ImageView -> ImageView -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ImageView
pPAttachments' Ptr ImageView -> Int -> Ptr ImageView
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr ImageView) (ImageView
e)) (Vector ImageView
attachments)
    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 ImageView) -> Ptr ImageView -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (FramebufferCreateInfo es)
p Ptr (FramebufferCreateInfo es) -> Int -> Ptr (Ptr ImageView)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr ImageView))) (Ptr ImageView
pPAttachments')
    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 Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (FramebufferCreateInfo es)
p Ptr (FramebufferCreateInfo es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Word32)) (Word32
width)
    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 Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (FramebufferCreateInfo es)
p Ptr (FramebufferCreateInfo es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 52 :: Ptr Word32)) (Word32
height)
    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 Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (FramebufferCreateInfo es)
p Ptr (FramebufferCreateInfo es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr Word32)) (Word32
layers)
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = 64
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr (FramebufferCreateInfo es) -> IO b -> IO b
pokeZeroCStruct p :: Ptr (FramebufferCreateInfo es)
p f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (FramebufferCreateInfo es)
p Ptr (FramebufferCreateInfo es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_FRAMEBUFFER_CREATE_INFO)
    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 (FramebufferCreateInfo es)
p Ptr (FramebufferCreateInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext'
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ ("pRenderPass" ::: Ptr RenderPass) -> RenderPass -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (FramebufferCreateInfo es)
p Ptr (FramebufferCreateInfo es)
-> Int -> "pRenderPass" ::: Ptr RenderPass
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr RenderPass)) (RenderPass
forall a. Zero a => a
zero)
    Ptr ImageView
pPAttachments' <- ((Ptr ImageView -> IO b) -> IO b) -> ContT b IO (Ptr ImageView)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr ImageView -> IO b) -> IO b) -> ContT b IO (Ptr ImageView))
-> ((Ptr ImageView -> IO b) -> IO b) -> ContT b IO (Ptr ImageView)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr ImageView -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @ImageView ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 8
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> ImageView -> IO ()) -> Vector ImageView -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: ImageView
e -> Ptr ImageView -> ImageView -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ImageView
pPAttachments' Ptr ImageView -> Int -> Ptr ImageView
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr ImageView) (ImageView
e)) (Vector ImageView
forall a. Monoid a => a
mempty)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ImageView) -> Ptr ImageView -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (FramebufferCreateInfo es)
p Ptr (FramebufferCreateInfo es) -> Int -> Ptr (Ptr ImageView)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr ImageView))) (Ptr ImageView
pPAttachments')
    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 Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (FramebufferCreateInfo es)
p Ptr (FramebufferCreateInfo es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: 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 Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (FramebufferCreateInfo es)
p Ptr (FramebufferCreateInfo es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 52 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (FramebufferCreateInfo es)
p Ptr (FramebufferCreateInfo es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr Word32)) (Word32
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 FramebufferCreateInfo es, PeekChain es) => FromCStruct (FramebufferCreateInfo es) where
  peekCStruct :: Ptr (FramebufferCreateInfo es) -> IO (FramebufferCreateInfo es)
peekCStruct p :: Ptr (FramebufferCreateInfo es)
p = do
    Ptr ()
pNext <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (FramebufferCreateInfo es)
p Ptr (FramebufferCreateInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ())))
    Chain es
next <- Ptr (Chain es) -> IO (Chain es)
forall (es :: [*]). PeekChain es => Ptr (Chain es) -> IO (Chain es)
peekChain (Ptr () -> Ptr (Chain es)
forall a b. Ptr a -> Ptr b
castPtr Ptr ()
pNext)
    FramebufferCreateFlags
flags <- Ptr FramebufferCreateFlags -> IO FramebufferCreateFlags
forall a. Storable a => Ptr a -> IO a
peek @FramebufferCreateFlags ((Ptr (FramebufferCreateInfo es)
p Ptr (FramebufferCreateInfo es) -> Int -> Ptr FramebufferCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr FramebufferCreateFlags))
    RenderPass
renderPass <- ("pRenderPass" ::: Ptr RenderPass) -> IO RenderPass
forall a. Storable a => Ptr a -> IO a
peek @RenderPass ((Ptr (FramebufferCreateInfo es)
p Ptr (FramebufferCreateInfo es)
-> Int -> "pRenderPass" ::: Ptr RenderPass
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr RenderPass))
    Word32
attachmentCount <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (FramebufferCreateInfo es)
p Ptr (FramebufferCreateInfo es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word32))
    Ptr ImageView
pAttachments <- Ptr (Ptr ImageView) -> IO (Ptr ImageView)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ImageView) ((Ptr (FramebufferCreateInfo es)
p Ptr (FramebufferCreateInfo es) -> Int -> Ptr (Ptr ImageView)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr ImageView)))
    Vector ImageView
pAttachments' <- Int -> (Int -> IO ImageView) -> IO (Vector ImageView)
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
attachmentCount) (\i :: Int
i -> Ptr ImageView -> IO ImageView
forall a. Storable a => Ptr a -> IO a
peek @ImageView ((Ptr ImageView
pAttachments Ptr ImageView -> Int -> Ptr ImageView
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr ImageView)))
    Word32
width <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (FramebufferCreateInfo es)
p Ptr (FramebufferCreateInfo es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Word32))
    Word32
height <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (FramebufferCreateInfo es)
p Ptr (FramebufferCreateInfo es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 52 :: Ptr Word32))
    Word32
layers <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (FramebufferCreateInfo es)
p Ptr (FramebufferCreateInfo es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr Word32))
    FramebufferCreateInfo es -> IO (FramebufferCreateInfo es)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (FramebufferCreateInfo es -> IO (FramebufferCreateInfo es))
-> FramebufferCreateInfo es -> IO (FramebufferCreateInfo es)
forall a b. (a -> b) -> a -> b
$ Chain es
-> FramebufferCreateFlags
-> RenderPass
-> Vector ImageView
-> Word32
-> Word32
-> Word32
-> FramebufferCreateInfo es
forall (es :: [*]).
Chain es
-> FramebufferCreateFlags
-> RenderPass
-> Vector ImageView
-> Word32
-> Word32
-> Word32
-> FramebufferCreateInfo es
FramebufferCreateInfo
             Chain es
next FramebufferCreateFlags
flags RenderPass
renderPass Vector ImageView
pAttachments' Word32
width Word32
height Word32
layers
instance es ~ '[] => Zero (FramebufferCreateInfo es) where
  zero :: FramebufferCreateInfo es
zero = Chain es
-> FramebufferCreateFlags
-> RenderPass
-> Vector ImageView
-> Word32
-> Word32
-> Word32
-> FramebufferCreateInfo es
forall (es :: [*]).
Chain es
-> FramebufferCreateFlags
-> RenderPass
-> Vector ImageView
-> Word32
-> Word32
-> Word32
-> FramebufferCreateInfo es
FramebufferCreateInfo
           ()
           FramebufferCreateFlags
forall a. Zero a => a
zero
           RenderPass
forall a. Zero a => a
zero
           Vector ImageView
forall a. Monoid a => a
mempty
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero