{-# language CPP #-}
module Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2 ( createRenderPass2
, cmdBeginRenderPass2
, cmdUseRenderPass2
, cmdNextSubpass2
, cmdEndRenderPass2
, AttachmentDescription2(..)
, AttachmentReference2(..)
, SubpassDescription2(..)
, SubpassDependency2(..)
, RenderPassCreateInfo2(..)
, SubpassBeginInfo(..)
, SubpassEndInfo(..)
, StructureType(..)
) 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 Data.Int (Int32)
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.CStruct.Extends (forgetExtensions)
import Vulkan.CStruct.Extends (peekSomeCStruct)
import Vulkan.CStruct.Extends (pokeSomeCStruct)
import Vulkan.CStruct.Extends (withSomeCStruct)
import Vulkan.NamedType ((:::))
import Vulkan.Core10.Enums.AccessFlagBits (AccessFlags)
import Vulkan.Core10.AllocationCallbacks (AllocationCallbacks)
import Vulkan.Core10.Enums.AttachmentDescriptionFlagBits (AttachmentDescriptionFlags)
import {-# SOURCE #-} Vulkan.Core12.Promoted_From_VK_KHR_separate_depth_stencil_layouts (AttachmentDescriptionStencilLayout)
import Vulkan.Core10.Enums.AttachmentLoadOp (AttachmentLoadOp)
import {-# SOURCE #-} Vulkan.Core12.Promoted_From_VK_KHR_separate_depth_stencil_layouts (AttachmentReferenceStencilLayout)
import Vulkan.Core10.Enums.AttachmentStoreOp (AttachmentStoreOp)
import Vulkan.CStruct.Extends (Chain)
import Vulkan.Core10.Handles (CommandBuffer)
import Vulkan.Core10.Handles (CommandBuffer(..))
import Vulkan.Core10.Handles (CommandBuffer_T)
import Vulkan.Core10.Enums.DependencyFlagBits (DependencyFlags)
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Dynamic (DeviceCmds(pVkCmdBeginRenderPass2))
import Vulkan.Dynamic (DeviceCmds(pVkCmdEndRenderPass2))
import Vulkan.Dynamic (DeviceCmds(pVkCmdNextSubpass2))
import Vulkan.Dynamic (DeviceCmds(pVkCreateRenderPass2))
import Vulkan.Core10.Handles (Device_T)
import Vulkan.CStruct.Extends (Extends)
import Vulkan.CStruct.Extends (Extendss)
import Vulkan.CStruct.Extends (Extensible(..))
import Vulkan.Core10.Enums.Format (Format)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.Enums.ImageAspectFlagBits (ImageAspectFlags)
import Vulkan.Core10.Enums.ImageLayout (ImageLayout)
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.CommandBufferBuilding (RenderPassBeginInfo)
import Vulkan.Core10.Enums.RenderPassCreateFlagBits (RenderPassCreateFlags)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_fragment_density_map (RenderPassFragmentDensityMapCreateInfoEXT)
import Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.Core10.Enums.SampleCountFlagBits (SampleCountFlagBits)
import Vulkan.CStruct.Extends (SomeStruct)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.SubpassContents (SubpassContents)
import {-# SOURCE #-} Vulkan.Core12.Promoted_From_VK_KHR_depth_stencil_resolve (SubpassDescriptionDepthStencilResolve)
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_ATTACHMENT_DESCRIPTION_2))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_ATTACHMENT_REFERENCE_2))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_RENDER_PASS_CREATE_INFO_2))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_SUBPASS_BEGIN_INFO))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_SUBPASS_DEPENDENCY_2))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_SUBPASS_DESCRIPTION_2))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_SUBPASS_END_INFO))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
import Vulkan.Core10.Enums.StructureType (StructureType(..))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkCreateRenderPass2
:: FunPtr (Ptr Device_T -> Ptr (RenderPassCreateInfo2 a) -> Ptr AllocationCallbacks -> Ptr RenderPass -> IO Result) -> Ptr Device_T -> Ptr (RenderPassCreateInfo2 a) -> Ptr AllocationCallbacks -> Ptr RenderPass -> IO Result
createRenderPass2 :: forall a io . (Extendss RenderPassCreateInfo2 a, PokeChain a, MonadIO io) => Device -> RenderPassCreateInfo2 a -> ("allocator" ::: Maybe AllocationCallbacks) -> io (RenderPass)
createRenderPass2 :: Device
-> RenderPassCreateInfo2 a
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io RenderPass
createRenderPass2 device :: Device
device createInfo :: RenderPassCreateInfo2 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 vkCreateRenderPass2Ptr :: FunPtr
(Ptr Device_T
-> ("pCreateInfo" ::: Ptr (RenderPassCreateInfo2 a))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pRenderPass" ::: Ptr RenderPass)
-> IO Result)
vkCreateRenderPass2Ptr = DeviceCmds
-> forall (a :: [*]).
FunPtr
(Ptr Device_T
-> ("pCreateInfo" ::: Ptr (RenderPassCreateInfo2 a))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pRenderPass" ::: Ptr RenderPass)
-> IO Result)
pVkCreateRenderPass2 (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 (RenderPassCreateInfo2 a))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pRenderPass" ::: Ptr RenderPass)
-> IO Result)
vkCreateRenderPass2Ptr FunPtr
(Ptr Device_T
-> ("pCreateInfo" ::: Ptr (RenderPassCreateInfo2 a))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pRenderPass" ::: Ptr RenderPass)
-> IO Result)
-> FunPtr
(Ptr Device_T
-> ("pCreateInfo" ::: Ptr (RenderPassCreateInfo2 a))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pRenderPass" ::: Ptr RenderPass)
-> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
(Ptr Device_T
-> ("pCreateInfo" ::: Ptr (RenderPassCreateInfo2 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 vkCreateRenderPass2 is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
let vkCreateRenderPass2' :: Ptr Device_T
-> ("pCreateInfo" ::: Ptr (RenderPassCreateInfo2 a))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pRenderPass" ::: Ptr RenderPass)
-> IO Result
vkCreateRenderPass2' = FunPtr
(Ptr Device_T
-> ("pCreateInfo" ::: Ptr (RenderPassCreateInfo2 a))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pRenderPass" ::: Ptr RenderPass)
-> IO Result)
-> Ptr Device_T
-> ("pCreateInfo" ::: Ptr (RenderPassCreateInfo2 a))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pRenderPass" ::: Ptr RenderPass)
-> IO Result
forall (a :: [*]).
FunPtr
(Ptr Device_T
-> Ptr (RenderPassCreateInfo2 a)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pRenderPass" ::: Ptr RenderPass)
-> IO Result)
-> Ptr Device_T
-> Ptr (RenderPassCreateInfo2 a)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pRenderPass" ::: Ptr RenderPass)
-> IO Result
mkVkCreateRenderPass2 FunPtr
(Ptr Device_T
-> ("pCreateInfo" ::: Ptr (RenderPassCreateInfo2 a))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pRenderPass" ::: Ptr RenderPass)
-> IO Result)
vkCreateRenderPass2Ptr
"pCreateInfo" ::: Ptr (RenderPassCreateInfo2 a)
pCreateInfo <- ((("pCreateInfo" ::: Ptr (RenderPassCreateInfo2 a))
-> IO RenderPass)
-> IO RenderPass)
-> ContT
RenderPass IO ("pCreateInfo" ::: Ptr (RenderPassCreateInfo2 a))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pCreateInfo" ::: Ptr (RenderPassCreateInfo2 a))
-> IO RenderPass)
-> IO RenderPass)
-> ContT
RenderPass IO ("pCreateInfo" ::: Ptr (RenderPassCreateInfo2 a)))
-> ((("pCreateInfo" ::: Ptr (RenderPassCreateInfo2 a))
-> IO RenderPass)
-> IO RenderPass)
-> ContT
RenderPass IO ("pCreateInfo" ::: Ptr (RenderPassCreateInfo2 a))
forall a b. (a -> b) -> a -> b
$ RenderPassCreateInfo2 a
-> (("pCreateInfo" ::: Ptr (RenderPassCreateInfo2 a))
-> IO RenderPass)
-> IO RenderPass
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (RenderPassCreateInfo2 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 (RenderPassCreateInfo2 a))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pRenderPass" ::: Ptr RenderPass)
-> IO Result
vkCreateRenderPass2' (Device -> Ptr Device_T
deviceHandle (Device
device)) "pCreateInfo" ::: Ptr (RenderPassCreateInfo2 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)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkCmdBeginRenderPass2
:: FunPtr (Ptr CommandBuffer_T -> Ptr (RenderPassBeginInfo a) -> Ptr SubpassBeginInfo -> IO ()) -> Ptr CommandBuffer_T -> Ptr (RenderPassBeginInfo a) -> Ptr SubpassBeginInfo -> IO ()
cmdBeginRenderPass2 :: forall a io . (Extendss RenderPassBeginInfo a, PokeChain a, MonadIO io) => CommandBuffer -> RenderPassBeginInfo a -> SubpassBeginInfo -> io ()
cmdBeginRenderPass2 :: CommandBuffer -> RenderPassBeginInfo a -> SubpassBeginInfo -> io ()
cmdBeginRenderPass2 commandBuffer :: CommandBuffer
commandBuffer renderPassBegin :: RenderPassBeginInfo a
renderPassBegin subpassBeginInfo :: SubpassBeginInfo
subpassBeginInfo = 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 vkCmdBeginRenderPass2Ptr :: FunPtr
(Ptr CommandBuffer_T
-> ("pRenderPassBegin" ::: Ptr (RenderPassBeginInfo a))
-> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> IO ())
vkCmdBeginRenderPass2Ptr = DeviceCmds
-> forall (a :: [*]).
FunPtr
(Ptr CommandBuffer_T
-> ("pRenderPassBegin" ::: Ptr (RenderPassBeginInfo a))
-> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> IO ())
pVkCmdBeginRenderPass2 (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
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 CommandBuffer_T
-> ("pRenderPassBegin" ::: Ptr (RenderPassBeginInfo a))
-> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> IO ())
vkCmdBeginRenderPass2Ptr FunPtr
(Ptr CommandBuffer_T
-> ("pRenderPassBegin" ::: Ptr (RenderPassBeginInfo a))
-> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> IO ())
-> FunPtr
(Ptr CommandBuffer_T
-> ("pRenderPassBegin" ::: Ptr (RenderPassBeginInfo a))
-> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
(Ptr CommandBuffer_T
-> ("pRenderPassBegin" ::: Ptr (RenderPassBeginInfo a))
-> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> 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 vkCmdBeginRenderPass2 is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
let vkCmdBeginRenderPass2' :: Ptr CommandBuffer_T
-> ("pRenderPassBegin" ::: Ptr (RenderPassBeginInfo a))
-> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> IO ()
vkCmdBeginRenderPass2' = FunPtr
(Ptr CommandBuffer_T
-> ("pRenderPassBegin" ::: Ptr (RenderPassBeginInfo a))
-> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> IO ())
-> Ptr CommandBuffer_T
-> ("pRenderPassBegin" ::: Ptr (RenderPassBeginInfo a))
-> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> IO ()
forall (a :: [*]).
FunPtr
(Ptr CommandBuffer_T
-> Ptr (RenderPassBeginInfo a)
-> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> IO ())
-> Ptr CommandBuffer_T
-> Ptr (RenderPassBeginInfo a)
-> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> IO ()
mkVkCmdBeginRenderPass2 FunPtr
(Ptr CommandBuffer_T
-> ("pRenderPassBegin" ::: Ptr (RenderPassBeginInfo a))
-> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> IO ())
vkCmdBeginRenderPass2Ptr
"pRenderPassBegin" ::: Ptr (RenderPassBeginInfo a)
pRenderPassBegin <- ((("pRenderPassBegin" ::: Ptr (RenderPassBeginInfo a)) -> IO ())
-> IO ())
-> ContT () IO ("pRenderPassBegin" ::: Ptr (RenderPassBeginInfo a))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pRenderPassBegin" ::: Ptr (RenderPassBeginInfo a)) -> IO ())
-> IO ())
-> ContT
() IO ("pRenderPassBegin" ::: Ptr (RenderPassBeginInfo a)))
-> ((("pRenderPassBegin" ::: Ptr (RenderPassBeginInfo a)) -> IO ())
-> IO ())
-> ContT () IO ("pRenderPassBegin" ::: Ptr (RenderPassBeginInfo a))
forall a b. (a -> b) -> a -> b
$ RenderPassBeginInfo a
-> (("pRenderPassBegin" ::: Ptr (RenderPassBeginInfo a)) -> IO ())
-> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (RenderPassBeginInfo a
renderPassBegin)
"pSubpassBeginInfo" ::: Ptr SubpassBeginInfo
pSubpassBeginInfo <- ((("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo) -> IO ())
-> IO ())
-> ContT () IO ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo) -> IO ())
-> IO ())
-> ContT () IO ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo))
-> ((("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo) -> IO ())
-> IO ())
-> ContT () IO ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
forall a b. (a -> b) -> a -> b
$ SubpassBeginInfo
-> (("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo) -> IO ())
-> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (SubpassBeginInfo
subpassBeginInfo)
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 CommandBuffer_T
-> ("pRenderPassBegin" ::: Ptr (RenderPassBeginInfo a))
-> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> IO ()
vkCmdBeginRenderPass2' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) "pRenderPassBegin" ::: Ptr (RenderPassBeginInfo a)
pRenderPassBegin "pSubpassBeginInfo" ::: Ptr SubpassBeginInfo
pSubpassBeginInfo
() -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()
cmdUseRenderPass2 :: forall a io r . (Extendss RenderPassBeginInfo a, PokeChain a, MonadIO io) => CommandBuffer -> RenderPassBeginInfo a -> SubpassBeginInfo -> SubpassEndInfo -> io r -> io r
cmdUseRenderPass2 :: CommandBuffer
-> RenderPassBeginInfo a
-> SubpassBeginInfo
-> SubpassEndInfo
-> io r
-> io r
cmdUseRenderPass2 commandBuffer :: CommandBuffer
commandBuffer pRenderPassBegin :: RenderPassBeginInfo a
pRenderPassBegin pSubpassBeginInfo :: SubpassBeginInfo
pSubpassBeginInfo pSubpassEndInfo :: SubpassEndInfo
pSubpassEndInfo a :: io r
a =
(CommandBuffer -> RenderPassBeginInfo a -> SubpassBeginInfo -> io ()
forall (a :: [*]) (io :: * -> *).
(Extendss RenderPassBeginInfo a, PokeChain a, MonadIO io) =>
CommandBuffer -> RenderPassBeginInfo a -> SubpassBeginInfo -> io ()
cmdBeginRenderPass2 CommandBuffer
commandBuffer RenderPassBeginInfo a
pRenderPassBegin SubpassBeginInfo
pSubpassBeginInfo) io () -> io r -> io r
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> io r
a io r -> io () -> io r
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* (CommandBuffer -> SubpassEndInfo -> io ()
forall (io :: * -> *).
MonadIO io =>
CommandBuffer -> SubpassEndInfo -> io ()
cmdEndRenderPass2 CommandBuffer
commandBuffer SubpassEndInfo
pSubpassEndInfo)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkCmdNextSubpass2
:: FunPtr (Ptr CommandBuffer_T -> Ptr SubpassBeginInfo -> Ptr SubpassEndInfo -> IO ()) -> Ptr CommandBuffer_T -> Ptr SubpassBeginInfo -> Ptr SubpassEndInfo -> IO ()
cmdNextSubpass2 :: forall io . MonadIO io => CommandBuffer -> SubpassBeginInfo -> SubpassEndInfo -> io ()
cmdNextSubpass2 :: CommandBuffer -> SubpassBeginInfo -> SubpassEndInfo -> io ()
cmdNextSubpass2 commandBuffer :: CommandBuffer
commandBuffer subpassBeginInfo :: SubpassBeginInfo
subpassBeginInfo subpassEndInfo :: SubpassEndInfo
subpassEndInfo = 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 vkCmdNextSubpass2Ptr :: FunPtr
(Ptr CommandBuffer_T
-> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> ("pSubpassEndInfo" ::: Ptr SubpassEndInfo)
-> IO ())
vkCmdNextSubpass2Ptr = DeviceCmds
-> FunPtr
(Ptr CommandBuffer_T
-> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> ("pSubpassEndInfo" ::: Ptr SubpassEndInfo)
-> IO ())
pVkCmdNextSubpass2 (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
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 CommandBuffer_T
-> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> ("pSubpassEndInfo" ::: Ptr SubpassEndInfo)
-> IO ())
vkCmdNextSubpass2Ptr FunPtr
(Ptr CommandBuffer_T
-> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> ("pSubpassEndInfo" ::: Ptr SubpassEndInfo)
-> IO ())
-> FunPtr
(Ptr CommandBuffer_T
-> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> ("pSubpassEndInfo" ::: Ptr SubpassEndInfo)
-> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
(Ptr CommandBuffer_T
-> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> ("pSubpassEndInfo" ::: Ptr SubpassEndInfo)
-> 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 vkCmdNextSubpass2 is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
let vkCmdNextSubpass2' :: Ptr CommandBuffer_T
-> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> ("pSubpassEndInfo" ::: Ptr SubpassEndInfo)
-> IO ()
vkCmdNextSubpass2' = FunPtr
(Ptr CommandBuffer_T
-> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> ("pSubpassEndInfo" ::: Ptr SubpassEndInfo)
-> IO ())
-> Ptr CommandBuffer_T
-> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> ("pSubpassEndInfo" ::: Ptr SubpassEndInfo)
-> IO ()
mkVkCmdNextSubpass2 FunPtr
(Ptr CommandBuffer_T
-> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> ("pSubpassEndInfo" ::: Ptr SubpassEndInfo)
-> IO ())
vkCmdNextSubpass2Ptr
"pSubpassBeginInfo" ::: Ptr SubpassBeginInfo
pSubpassBeginInfo <- ((("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo) -> IO ())
-> IO ())
-> ContT () IO ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo) -> IO ())
-> IO ())
-> ContT () IO ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo))
-> ((("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo) -> IO ())
-> IO ())
-> ContT () IO ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
forall a b. (a -> b) -> a -> b
$ SubpassBeginInfo
-> (("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo) -> IO ())
-> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (SubpassBeginInfo
subpassBeginInfo)
"pSubpassEndInfo" ::: Ptr SubpassEndInfo
pSubpassEndInfo <- ((("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO ()) -> IO ())
-> ContT () IO ("pSubpassEndInfo" ::: Ptr SubpassEndInfo)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO ()) -> IO ())
-> ContT () IO ("pSubpassEndInfo" ::: Ptr SubpassEndInfo))
-> ((("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO ()) -> IO ())
-> ContT () IO ("pSubpassEndInfo" ::: Ptr SubpassEndInfo)
forall a b. (a -> b) -> a -> b
$ SubpassEndInfo
-> (("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO ()) -> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (SubpassEndInfo
subpassEndInfo)
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 CommandBuffer_T
-> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> ("pSubpassEndInfo" ::: Ptr SubpassEndInfo)
-> IO ()
vkCmdNextSubpass2' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) "pSubpassBeginInfo" ::: Ptr SubpassBeginInfo
pSubpassBeginInfo "pSubpassEndInfo" ::: Ptr SubpassEndInfo
pSubpassEndInfo
() -> 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" mkVkCmdEndRenderPass2
:: FunPtr (Ptr CommandBuffer_T -> Ptr SubpassEndInfo -> IO ()) -> Ptr CommandBuffer_T -> Ptr SubpassEndInfo -> IO ()
cmdEndRenderPass2 :: forall io . MonadIO io => CommandBuffer -> SubpassEndInfo -> io ()
cmdEndRenderPass2 :: CommandBuffer -> SubpassEndInfo -> io ()
cmdEndRenderPass2 commandBuffer :: CommandBuffer
commandBuffer subpassEndInfo :: SubpassEndInfo
subpassEndInfo = 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 vkCmdEndRenderPass2Ptr :: FunPtr
(Ptr CommandBuffer_T
-> ("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO ())
vkCmdEndRenderPass2Ptr = DeviceCmds
-> FunPtr
(Ptr CommandBuffer_T
-> ("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO ())
pVkCmdEndRenderPass2 (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
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 CommandBuffer_T
-> ("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO ())
vkCmdEndRenderPass2Ptr FunPtr
(Ptr CommandBuffer_T
-> ("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO ())
-> FunPtr
(Ptr CommandBuffer_T
-> ("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
(Ptr CommandBuffer_T
-> ("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> 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 vkCmdEndRenderPass2 is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
let vkCmdEndRenderPass2' :: Ptr CommandBuffer_T
-> ("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO ()
vkCmdEndRenderPass2' = FunPtr
(Ptr CommandBuffer_T
-> ("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO ())
-> Ptr CommandBuffer_T
-> ("pSubpassEndInfo" ::: Ptr SubpassEndInfo)
-> IO ()
mkVkCmdEndRenderPass2 FunPtr
(Ptr CommandBuffer_T
-> ("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO ())
vkCmdEndRenderPass2Ptr
"pSubpassEndInfo" ::: Ptr SubpassEndInfo
pSubpassEndInfo <- ((("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO ()) -> IO ())
-> ContT () IO ("pSubpassEndInfo" ::: Ptr SubpassEndInfo)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO ()) -> IO ())
-> ContT () IO ("pSubpassEndInfo" ::: Ptr SubpassEndInfo))
-> ((("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO ()) -> IO ())
-> ContT () IO ("pSubpassEndInfo" ::: Ptr SubpassEndInfo)
forall a b. (a -> b) -> a -> b
$ SubpassEndInfo
-> (("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO ()) -> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (SubpassEndInfo
subpassEndInfo)
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 CommandBuffer_T
-> ("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO ()
vkCmdEndRenderPass2' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) "pSubpassEndInfo" ::: Ptr SubpassEndInfo
pSubpassEndInfo
() -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()
data AttachmentDescription2 (es :: [Type]) = AttachmentDescription2
{
AttachmentDescription2 es -> Chain es
next :: Chain es
,
AttachmentDescription2 es -> AttachmentDescriptionFlags
flags :: AttachmentDescriptionFlags
,
AttachmentDescription2 es -> Format
format :: Format
,
AttachmentDescription2 es -> SampleCountFlagBits
samples :: SampleCountFlagBits
,
AttachmentDescription2 es -> AttachmentLoadOp
loadOp :: AttachmentLoadOp
,
AttachmentDescription2 es -> AttachmentStoreOp
storeOp :: AttachmentStoreOp
,
AttachmentDescription2 es -> AttachmentLoadOp
stencilLoadOp :: AttachmentLoadOp
,
AttachmentDescription2 es -> AttachmentStoreOp
stencilStoreOp :: AttachmentStoreOp
,
AttachmentDescription2 es -> ImageLayout
initialLayout :: ImageLayout
,
AttachmentDescription2 es -> ImageLayout
finalLayout :: ImageLayout
}
deriving (Typeable)
deriving instance Show (Chain es) => Show (AttachmentDescription2 es)
instance Extensible AttachmentDescription2 where
extensibleType :: StructureType
extensibleType = StructureType
STRUCTURE_TYPE_ATTACHMENT_DESCRIPTION_2
setNext :: AttachmentDescription2 ds -> Chain es -> AttachmentDescription2 es
setNext x :: AttachmentDescription2 ds
x next :: Chain es
next = AttachmentDescription2 ds
x{$sel:next:AttachmentDescription2 :: Chain es
next = Chain es
next}
getNext :: AttachmentDescription2 es -> Chain es
getNext AttachmentDescription2{..} = Chain es
next
extends :: forall e b proxy. Typeable e => proxy e -> (Extends AttachmentDescription2 e => b) -> Maybe b
extends :: proxy e -> (Extends AttachmentDescription2 e => b) -> Maybe b
extends _ f :: Extends AttachmentDescription2 e => b
f
| Just Refl <- (Typeable e, Typeable AttachmentDescriptionStencilLayout) =>
Maybe (e :~: AttachmentDescriptionStencilLayout)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @AttachmentDescriptionStencilLayout = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends AttachmentDescription2 e => b
f
| Bool
otherwise = Maybe b
forall a. Maybe a
Nothing
instance (Extendss AttachmentDescription2 es, PokeChain es) => ToCStruct (AttachmentDescription2 es) where
withCStruct :: AttachmentDescription2 es
-> (Ptr (AttachmentDescription2 es) -> IO b) -> IO b
withCStruct x :: AttachmentDescription2 es
x f :: Ptr (AttachmentDescription2 es) -> IO b
f = Int -> Int -> (Ptr (AttachmentDescription2 es) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 56 8 ((Ptr (AttachmentDescription2 es) -> IO b) -> IO b)
-> (Ptr (AttachmentDescription2 es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr (AttachmentDescription2 es)
p -> Ptr (AttachmentDescription2 es)
-> AttachmentDescription2 es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (AttachmentDescription2 es)
p AttachmentDescription2 es
x (Ptr (AttachmentDescription2 es) -> IO b
f Ptr (AttachmentDescription2 es)
p)
pokeCStruct :: Ptr (AttachmentDescription2 es)
-> AttachmentDescription2 es -> IO b -> IO b
pokeCStruct p :: Ptr (AttachmentDescription2 es)
p AttachmentDescription2{..} 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 (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ATTACHMENT_DESCRIPTION_2)
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 (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 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 AttachmentDescriptionFlags
-> AttachmentDescriptionFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es)
-> Int -> Ptr AttachmentDescriptionFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr AttachmentDescriptionFlags)) (AttachmentDescriptionFlags
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 Format -> Format -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr Format
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Format)) (Format
format)
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 SampleCountFlagBits -> SampleCountFlagBits -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr SampleCountFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr SampleCountFlagBits)) (SampleCountFlagBits
samples)
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 AttachmentLoadOp -> AttachmentLoadOp -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr AttachmentLoadOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr AttachmentLoadOp)) (AttachmentLoadOp
loadOp)
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 AttachmentStoreOp -> AttachmentStoreOp -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr AttachmentStoreOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr AttachmentStoreOp)) (AttachmentStoreOp
storeOp)
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 AttachmentLoadOp -> AttachmentLoadOp -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr AttachmentLoadOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr AttachmentLoadOp)) (AttachmentLoadOp
stencilLoadOp)
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 AttachmentStoreOp -> AttachmentStoreOp -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr AttachmentStoreOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr AttachmentStoreOp)) (AttachmentStoreOp
stencilStoreOp)
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 ImageLayout -> ImageLayout -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr ImageLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr ImageLayout)) (ImageLayout
initialLayout)
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 ImageLayout -> ImageLayout -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr ImageLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr ImageLayout)) (ImageLayout
finalLayout)
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 = 56
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: Ptr (AttachmentDescription2 es) -> IO b -> IO b
pokeZeroCStruct p :: Ptr (AttachmentDescription2 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 (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ATTACHMENT_DESCRIPTION_2)
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 (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 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 Format -> Format -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr Format
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Format)) (Format
forall a. Zero a => a
zero)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr SampleCountFlagBits -> SampleCountFlagBits -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr SampleCountFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr SampleCountFlagBits)) (SampleCountFlagBits
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 AttachmentLoadOp -> AttachmentLoadOp -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr AttachmentLoadOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr AttachmentLoadOp)) (AttachmentLoadOp
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 AttachmentStoreOp -> AttachmentStoreOp -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr AttachmentStoreOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr AttachmentStoreOp)) (AttachmentStoreOp
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 AttachmentLoadOp -> AttachmentLoadOp -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr AttachmentLoadOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr AttachmentLoadOp)) (AttachmentLoadOp
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 AttachmentStoreOp -> AttachmentStoreOp -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr AttachmentStoreOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr AttachmentStoreOp)) (AttachmentStoreOp
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 ImageLayout -> ImageLayout -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr ImageLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr ImageLayout)) (ImageLayout
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 ImageLayout -> ImageLayout -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr ImageLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr ImageLayout)) (ImageLayout
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 AttachmentDescription2 es, PeekChain es) => FromCStruct (AttachmentDescription2 es) where
peekCStruct :: Ptr (AttachmentDescription2 es) -> IO (AttachmentDescription2 es)
peekCStruct p :: Ptr (AttachmentDescription2 es)
p = do
Ptr ()
pNext <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 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)
AttachmentDescriptionFlags
flags <- Ptr AttachmentDescriptionFlags -> IO AttachmentDescriptionFlags
forall a. Storable a => Ptr a -> IO a
peek @AttachmentDescriptionFlags ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es)
-> Int -> Ptr AttachmentDescriptionFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr AttachmentDescriptionFlags))
Format
format <- Ptr Format -> IO Format
forall a. Storable a => Ptr a -> IO a
peek @Format ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr Format
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Format))
SampleCountFlagBits
samples <- Ptr SampleCountFlagBits -> IO SampleCountFlagBits
forall a. Storable a => Ptr a -> IO a
peek @SampleCountFlagBits ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr SampleCountFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr SampleCountFlagBits))
AttachmentLoadOp
loadOp <- Ptr AttachmentLoadOp -> IO AttachmentLoadOp
forall a. Storable a => Ptr a -> IO a
peek @AttachmentLoadOp ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr AttachmentLoadOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr AttachmentLoadOp))
AttachmentStoreOp
storeOp <- Ptr AttachmentStoreOp -> IO AttachmentStoreOp
forall a. Storable a => Ptr a -> IO a
peek @AttachmentStoreOp ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr AttachmentStoreOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr AttachmentStoreOp))
AttachmentLoadOp
stencilLoadOp <- Ptr AttachmentLoadOp -> IO AttachmentLoadOp
forall a. Storable a => Ptr a -> IO a
peek @AttachmentLoadOp ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr AttachmentLoadOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr AttachmentLoadOp))
AttachmentStoreOp
stencilStoreOp <- Ptr AttachmentStoreOp -> IO AttachmentStoreOp
forall a. Storable a => Ptr a -> IO a
peek @AttachmentStoreOp ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr AttachmentStoreOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr AttachmentStoreOp))
ImageLayout
initialLayout <- Ptr ImageLayout -> IO ImageLayout
forall a. Storable a => Ptr a -> IO a
peek @ImageLayout ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr ImageLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr ImageLayout))
ImageLayout
finalLayout <- Ptr ImageLayout -> IO ImageLayout
forall a. Storable a => Ptr a -> IO a
peek @ImageLayout ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr ImageLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr ImageLayout))
AttachmentDescription2 es -> IO (AttachmentDescription2 es)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AttachmentDescription2 es -> IO (AttachmentDescription2 es))
-> AttachmentDescription2 es -> IO (AttachmentDescription2 es)
forall a b. (a -> b) -> a -> b
$ Chain es
-> AttachmentDescriptionFlags
-> Format
-> SampleCountFlagBits
-> AttachmentLoadOp
-> AttachmentStoreOp
-> AttachmentLoadOp
-> AttachmentStoreOp
-> ImageLayout
-> ImageLayout
-> AttachmentDescription2 es
forall (es :: [*]).
Chain es
-> AttachmentDescriptionFlags
-> Format
-> SampleCountFlagBits
-> AttachmentLoadOp
-> AttachmentStoreOp
-> AttachmentLoadOp
-> AttachmentStoreOp
-> ImageLayout
-> ImageLayout
-> AttachmentDescription2 es
AttachmentDescription2
Chain es
next AttachmentDescriptionFlags
flags Format
format SampleCountFlagBits
samples AttachmentLoadOp
loadOp AttachmentStoreOp
storeOp AttachmentLoadOp
stencilLoadOp AttachmentStoreOp
stencilStoreOp ImageLayout
initialLayout ImageLayout
finalLayout
instance es ~ '[] => Zero (AttachmentDescription2 es) where
zero :: AttachmentDescription2 es
zero = Chain es
-> AttachmentDescriptionFlags
-> Format
-> SampleCountFlagBits
-> AttachmentLoadOp
-> AttachmentStoreOp
-> AttachmentLoadOp
-> AttachmentStoreOp
-> ImageLayout
-> ImageLayout
-> AttachmentDescription2 es
forall (es :: [*]).
Chain es
-> AttachmentDescriptionFlags
-> Format
-> SampleCountFlagBits
-> AttachmentLoadOp
-> AttachmentStoreOp
-> AttachmentLoadOp
-> AttachmentStoreOp
-> ImageLayout
-> ImageLayout
-> AttachmentDescription2 es
AttachmentDescription2
()
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 AttachmentReference2 (es :: [Type]) = AttachmentReference2
{
AttachmentReference2 es -> Chain es
next :: Chain es
,
AttachmentReference2 es -> Word32
attachment :: Word32
,
AttachmentReference2 es -> ImageLayout
layout :: ImageLayout
,
AttachmentReference2 es -> ImageAspectFlags
aspectMask :: ImageAspectFlags
}
deriving (Typeable)
deriving instance Show (Chain es) => Show (AttachmentReference2 es)
instance Extensible AttachmentReference2 where
extensibleType :: StructureType
extensibleType = StructureType
STRUCTURE_TYPE_ATTACHMENT_REFERENCE_2
setNext :: AttachmentReference2 ds -> Chain es -> AttachmentReference2 es
setNext x :: AttachmentReference2 ds
x next :: Chain es
next = AttachmentReference2 ds
x{$sel:next:AttachmentReference2 :: Chain es
next = Chain es
next}
getNext :: AttachmentReference2 es -> Chain es
getNext AttachmentReference2{..} = Chain es
next
extends :: forall e b proxy. Typeable e => proxy e -> (Extends AttachmentReference2 e => b) -> Maybe b
extends :: proxy e -> (Extends AttachmentReference2 e => b) -> Maybe b
extends _ f :: Extends AttachmentReference2 e => b
f
| Just Refl <- (Typeable e, Typeable AttachmentReferenceStencilLayout) =>
Maybe (e :~: AttachmentReferenceStencilLayout)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @AttachmentReferenceStencilLayout = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends AttachmentReference2 e => b
f
| Bool
otherwise = Maybe b
forall a. Maybe a
Nothing
instance (Extendss AttachmentReference2 es, PokeChain es) => ToCStruct (AttachmentReference2 es) where
withCStruct :: AttachmentReference2 es
-> (Ptr (AttachmentReference2 es) -> IO b) -> IO b
withCStruct x :: AttachmentReference2 es
x f :: Ptr (AttachmentReference2 es) -> IO b
f = Int -> Int -> (Ptr (AttachmentReference2 es) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 32 8 ((Ptr (AttachmentReference2 es) -> IO b) -> IO b)
-> (Ptr (AttachmentReference2 es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr (AttachmentReference2 es)
p -> Ptr (AttachmentReference2 es)
-> AttachmentReference2 es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (AttachmentReference2 es)
p AttachmentReference2 es
x (Ptr (AttachmentReference2 es) -> IO b
f Ptr (AttachmentReference2 es)
p)
pokeCStruct :: Ptr (AttachmentReference2 es)
-> AttachmentReference2 es -> IO b -> IO b
pokeCStruct p :: Ptr (AttachmentReference2 es)
p AttachmentReference2{..} 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 (AttachmentReference2 es)
p Ptr (AttachmentReference2 es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ATTACHMENT_REFERENCE_2)
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 (AttachmentReference2 es)
p Ptr (AttachmentReference2 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 Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AttachmentReference2 es)
p Ptr (AttachmentReference2 es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) (Word32
attachment)
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 ImageLayout -> ImageLayout -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AttachmentReference2 es)
p Ptr (AttachmentReference2 es) -> Int -> Ptr ImageLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr ImageLayout)) (ImageLayout
layout)
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 ImageAspectFlags -> ImageAspectFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AttachmentReference2 es)
p Ptr (AttachmentReference2 es) -> Int -> Ptr ImageAspectFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr ImageAspectFlags)) (ImageAspectFlags
aspectMask)
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 = 32
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: Ptr (AttachmentReference2 es) -> IO b -> IO b
pokeZeroCStruct p :: Ptr (AttachmentReference2 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 (AttachmentReference2 es)
p Ptr (AttachmentReference2 es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ATTACHMENT_REFERENCE_2)
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 (AttachmentReference2 es)
p Ptr (AttachmentReference2 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 Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AttachmentReference2 es)
p Ptr (AttachmentReference2 es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: 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 ImageLayout -> ImageLayout -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AttachmentReference2 es)
p Ptr (AttachmentReference2 es) -> Int -> Ptr ImageLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr ImageLayout)) (ImageLayout
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 ImageAspectFlags -> ImageAspectFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AttachmentReference2 es)
p Ptr (AttachmentReference2 es) -> Int -> Ptr ImageAspectFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr ImageAspectFlags)) (ImageAspectFlags
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 AttachmentReference2 es, PeekChain es) => FromCStruct (AttachmentReference2 es) where
peekCStruct :: Ptr (AttachmentReference2 es) -> IO (AttachmentReference2 es)
peekCStruct p :: Ptr (AttachmentReference2 es)
p = do
Ptr ()
pNext <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (AttachmentReference2 es)
p Ptr (AttachmentReference2 es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ())))
Chain es
next <- Ptr (Chain es) -> IO (Chain es)
forall (es :: [*]). PeekChain es => Ptr (Chain es) -> IO (Chain es)
peekChain (Ptr () -> Ptr (Chain es)
forall a b. Ptr a -> Ptr b
castPtr Ptr ()
pNext)
Word32
attachment <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (AttachmentReference2 es)
p Ptr (AttachmentReference2 es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32))
ImageLayout
layout <- Ptr ImageLayout -> IO ImageLayout
forall a. Storable a => Ptr a -> IO a
peek @ImageLayout ((Ptr (AttachmentReference2 es)
p Ptr (AttachmentReference2 es) -> Int -> Ptr ImageLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr ImageLayout))
ImageAspectFlags
aspectMask <- Ptr ImageAspectFlags -> IO ImageAspectFlags
forall a. Storable a => Ptr a -> IO a
peek @ImageAspectFlags ((Ptr (AttachmentReference2 es)
p Ptr (AttachmentReference2 es) -> Int -> Ptr ImageAspectFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr ImageAspectFlags))
AttachmentReference2 es -> IO (AttachmentReference2 es)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AttachmentReference2 es -> IO (AttachmentReference2 es))
-> AttachmentReference2 es -> IO (AttachmentReference2 es)
forall a b. (a -> b) -> a -> b
$ Chain es
-> Word32
-> ImageLayout
-> ImageAspectFlags
-> AttachmentReference2 es
forall (es :: [*]).
Chain es
-> Word32
-> ImageLayout
-> ImageAspectFlags
-> AttachmentReference2 es
AttachmentReference2
Chain es
next Word32
attachment ImageLayout
layout ImageAspectFlags
aspectMask
instance es ~ '[] => Zero (AttachmentReference2 es) where
zero :: AttachmentReference2 es
zero = Chain es
-> Word32
-> ImageLayout
-> ImageAspectFlags
-> AttachmentReference2 es
forall (es :: [*]).
Chain es
-> Word32
-> ImageLayout
-> ImageAspectFlags
-> AttachmentReference2 es
AttachmentReference2
()
Word32
forall a. Zero a => a
zero
ImageLayout
forall a. Zero a => a
zero
ImageAspectFlags
forall a. Zero a => a
zero
data SubpassDescription2 (es :: [Type]) = SubpassDescription2
{
SubpassDescription2 es -> Chain es
next :: Chain es
,
SubpassDescription2 es -> SubpassDescriptionFlags
flags :: SubpassDescriptionFlags
,
SubpassDescription2 es -> PipelineBindPoint
pipelineBindPoint :: PipelineBindPoint
,
SubpassDescription2 es -> Word32
viewMask :: Word32
,
SubpassDescription2 es -> Vector (SomeStruct AttachmentReference2)
inputAttachments :: Vector (SomeStruct AttachmentReference2)
,
SubpassDescription2 es -> Vector (SomeStruct AttachmentReference2)
colorAttachments :: Vector (SomeStruct AttachmentReference2)
,
SubpassDescription2 es -> Vector (SomeStruct AttachmentReference2)
resolveAttachments :: Vector (SomeStruct AttachmentReference2)
,
SubpassDescription2 es -> Maybe (SomeStruct AttachmentReference2)
depthStencilAttachment :: Maybe (SomeStruct AttachmentReference2)
,
SubpassDescription2 es -> Vector Word32
preserveAttachments :: Vector Word32
}
deriving (Typeable)
deriving instance Show (Chain es) => Show (SubpassDescription2 es)
instance Extensible SubpassDescription2 where
extensibleType :: StructureType
extensibleType = StructureType
STRUCTURE_TYPE_SUBPASS_DESCRIPTION_2
setNext :: SubpassDescription2 ds -> Chain es -> SubpassDescription2 es
setNext x :: SubpassDescription2 ds
x next :: Chain es
next = SubpassDescription2 ds
x{$sel:next:SubpassDescription2 :: Chain es
next = Chain es
next}
getNext :: SubpassDescription2 es -> Chain es
getNext SubpassDescription2{..} = Chain es
next
extends :: forall e b proxy. Typeable e => proxy e -> (Extends SubpassDescription2 e => b) -> Maybe b
extends :: proxy e -> (Extends SubpassDescription2 e => b) -> Maybe b
extends _ f :: Extends SubpassDescription2 e => b
f
| Just Refl <- (Typeable e, Typeable SubpassDescriptionDepthStencilResolve) =>
Maybe (e :~: SubpassDescriptionDepthStencilResolve)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @SubpassDescriptionDepthStencilResolve = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends SubpassDescription2 e => b
f
| Bool
otherwise = Maybe b
forall a. Maybe a
Nothing
instance (Extendss SubpassDescription2 es, PokeChain es) => ToCStruct (SubpassDescription2 es) where
withCStruct :: SubpassDescription2 es
-> (Ptr (SubpassDescription2 es) -> IO b) -> IO b
withCStruct x :: SubpassDescription2 es
x f :: Ptr (SubpassDescription2 es) -> IO b
f = Int -> Int -> (Ptr (SubpassDescription2 es) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 88 8 ((Ptr (SubpassDescription2 es) -> IO b) -> IO b)
-> (Ptr (SubpassDescription2 es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr (SubpassDescription2 es)
p -> Ptr (SubpassDescription2 es)
-> SubpassDescription2 es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (SubpassDescription2 es)
p SubpassDescription2 es
x (Ptr (SubpassDescription2 es) -> IO b
f Ptr (SubpassDescription2 es)
p)
pokeCStruct :: Ptr (SubpassDescription2 es)
-> SubpassDescription2 es -> IO b -> IO b
pokeCStruct p :: Ptr (SubpassDescription2 es)
p SubpassDescription2{..} 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 (SubpassDescription2 es)
p Ptr (SubpassDescription2 es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SUBPASS_DESCRIPTION_2)
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 (SubpassDescription2 es)
p Ptr (SubpassDescription2 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 SubpassDescriptionFlags -> SubpassDescriptionFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 es) -> Int -> Ptr SubpassDescriptionFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: 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 (SubpassDescription2 es)
p Ptr (SubpassDescription2 es) -> Int -> Ptr PipelineBindPoint
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: 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 (SubpassDescription2 es)
p Ptr (SubpassDescription2 es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32)) (Word32
viewMask)
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 (SubpassDescription2 es)
p Ptr (SubpassDescription2 es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Word32)) ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector (SomeStruct AttachmentReference2) -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector (SomeStruct AttachmentReference2) -> Int)
-> Vector (SomeStruct AttachmentReference2) -> Int
forall a b. (a -> b) -> a -> b
$ (Vector (SomeStruct AttachmentReference2)
inputAttachments)) :: Word32))
Ptr (AttachmentReference2 Any)
pPInputAttachments' <- ((Ptr (AttachmentReference2 Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (AttachmentReference2 Any))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (AttachmentReference2 Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (AttachmentReference2 Any)))
-> ((Ptr (AttachmentReference2 Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (AttachmentReference2 Any))
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr (AttachmentReference2 Any) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(AttachmentReference2 _) ((Vector (SomeStruct AttachmentReference2) -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector (SomeStruct AttachmentReference2)
inputAttachments)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 32) 8
(Int -> SomeStruct AttachmentReference2 -> ContT b IO ())
-> Vector (SomeStruct AttachmentReference2) -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SomeStruct AttachmentReference2
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 (SomeStruct AttachmentReference2)
-> SomeStruct AttachmentReference2 -> IO b -> IO b
forall (a :: [*] -> *) b.
(forall (es :: [*]).
(Extendss a es, PokeChain es) =>
ToCStruct (a es)) =>
Ptr (SomeStruct a) -> SomeStruct a -> IO b -> IO b
pokeSomeCStruct (Ptr (AttachmentReference2 Any)
-> Ptr (SomeStruct AttachmentReference2)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (AttachmentReference2 Any)
pPInputAttachments' Ptr (AttachmentReference2 Any)
-> Int -> Ptr (AttachmentReference2 _)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (32 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (AttachmentReference2 _))) (SomeStruct AttachmentReference2
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 (SomeStruct AttachmentReference2)
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 (AttachmentReference2 Any))
-> Ptr (AttachmentReference2 Any) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 es)
-> Int -> Ptr (Ptr (AttachmentReference2 _))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (Ptr (AttachmentReference2 _)))) (Ptr (AttachmentReference2 Any)
pPInputAttachments')
let pColorAttachmentsLength :: Int
pColorAttachmentsLength = Vector (SomeStruct AttachmentReference2) -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector (SomeStruct AttachmentReference2) -> Int)
-> Vector (SomeStruct AttachmentReference2) -> Int
forall a b. (a -> b) -> a -> b
$ (Vector (SomeStruct AttachmentReference2)
colorAttachments)
let pResolveAttachmentsLength :: Int
pResolveAttachmentsLength = Vector (SomeStruct AttachmentReference2) -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector (SomeStruct AttachmentReference2) -> Int)
-> Vector (SomeStruct AttachmentReference2) -> Int
forall a b. (a -> b) -> a -> b
$ (Vector (SomeStruct AttachmentReference2)
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 (SubpassDescription2 es)
p Ptr (SubpassDescription2 es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Word32)) ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
pColorAttachmentsLength :: Word32))
Ptr (AttachmentReference2 Any)
pPColorAttachments' <- ((Ptr (AttachmentReference2 Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (AttachmentReference2 Any))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (AttachmentReference2 Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (AttachmentReference2 Any)))
-> ((Ptr (AttachmentReference2 Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (AttachmentReference2 Any))
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr (AttachmentReference2 Any) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(AttachmentReference2 _) ((Vector (SomeStruct AttachmentReference2) -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector (SomeStruct AttachmentReference2)
colorAttachments)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 32) 8
(Int -> SomeStruct AttachmentReference2 -> ContT b IO ())
-> Vector (SomeStruct AttachmentReference2) -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SomeStruct AttachmentReference2
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 (SomeStruct AttachmentReference2)
-> SomeStruct AttachmentReference2 -> IO b -> IO b
forall (a :: [*] -> *) b.
(forall (es :: [*]).
(Extendss a es, PokeChain es) =>
ToCStruct (a es)) =>
Ptr (SomeStruct a) -> SomeStruct a -> IO b -> IO b
pokeSomeCStruct (Ptr (AttachmentReference2 Any)
-> Ptr (SomeStruct AttachmentReference2)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (AttachmentReference2 Any)
pPColorAttachments' Ptr (AttachmentReference2 Any)
-> Int -> Ptr (AttachmentReference2 _)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (32 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (AttachmentReference2 _))) (SomeStruct AttachmentReference2
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 (SomeStruct AttachmentReference2)
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 (AttachmentReference2 Any))
-> Ptr (AttachmentReference2 Any) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 es)
-> Int -> Ptr (Ptr (AttachmentReference2 _))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr (Ptr (AttachmentReference2 _)))) (Ptr (AttachmentReference2 Any)
pPColorAttachments')
Ptr (AttachmentReference2 Any)
pResolveAttachments'' <- if Vector (SomeStruct AttachmentReference2) -> Bool
forall a. Vector a -> Bool
Data.Vector.null (Vector (SomeStruct AttachmentReference2)
resolveAttachments)
then Ptr (AttachmentReference2 Any)
-> ContT b IO (Ptr (AttachmentReference2 Any))
forall (f :: * -> *) a. Applicative f => a -> f a
pure Ptr (AttachmentReference2 Any)
forall a. Ptr a
nullPtr
else do
Ptr (AttachmentReference2 Any)
pPResolveAttachments <- ((Ptr (AttachmentReference2 Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (AttachmentReference2 Any))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (AttachmentReference2 Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (AttachmentReference2 Any)))
-> ((Ptr (AttachmentReference2 Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (AttachmentReference2 Any))
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr (AttachmentReference2 Any) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(AttachmentReference2 _) (((Vector (SomeStruct AttachmentReference2) -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector (SomeStruct AttachmentReference2)
resolveAttachments))) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 32) 8
(Int -> SomeStruct AttachmentReference2 -> ContT b IO ())
-> Vector (SomeStruct AttachmentReference2) -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SomeStruct AttachmentReference2
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 (SomeStruct AttachmentReference2)
-> SomeStruct AttachmentReference2 -> IO b -> IO b
forall (a :: [*] -> *) b.
(forall (es :: [*]).
(Extendss a es, PokeChain es) =>
ToCStruct (a es)) =>
Ptr (SomeStruct a) -> SomeStruct a -> IO b -> IO b
pokeSomeCStruct (Ptr (AttachmentReference2 Any)
-> Ptr (SomeStruct AttachmentReference2)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (AttachmentReference2 Any)
pPResolveAttachments Ptr (AttachmentReference2 Any)
-> Int -> Ptr (AttachmentReference2 _)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (32 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (AttachmentReference2 _))) (SomeStruct AttachmentReference2
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 (SomeStruct AttachmentReference2)
resolveAttachments))
Ptr (AttachmentReference2 Any)
-> ContT b IO (Ptr (AttachmentReference2 Any))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Ptr (AttachmentReference2 Any)
-> ContT b IO (Ptr (AttachmentReference2 Any)))
-> Ptr (AttachmentReference2 Any)
-> ContT b IO (Ptr (AttachmentReference2 Any))
forall a b. (a -> b) -> a -> b
$ Ptr (AttachmentReference2 Any)
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 (AttachmentReference2 Any))
-> Ptr (AttachmentReference2 Any) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 es)
-> Int -> Ptr (Ptr (AttachmentReference2 _))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr (Ptr (AttachmentReference2 _)))) Ptr (AttachmentReference2 Any)
pResolveAttachments''
Ptr (AttachmentReference2 '[])
pDepthStencilAttachment'' <- case (Maybe (SomeStruct AttachmentReference2)
depthStencilAttachment) of
Nothing -> Ptr (AttachmentReference2 '[])
-> ContT b IO (Ptr (AttachmentReference2 '[]))
forall (f :: * -> *) a. Applicative f => a -> f a
pure Ptr (AttachmentReference2 '[])
forall a. Ptr a
nullPtr
Just j :: SomeStruct AttachmentReference2
j -> ((Ptr (AttachmentReference2 '[]) -> IO b) -> IO b)
-> ContT b IO (Ptr (AttachmentReference2 '[]))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT @_ @_ @(Ptr (AttachmentReference2 '[])) (((Ptr (AttachmentReference2 '[]) -> IO b) -> IO b)
-> ContT b IO (Ptr (AttachmentReference2 '[])))
-> ((Ptr (AttachmentReference2 '[]) -> IO b) -> IO b)
-> ContT b IO (Ptr (AttachmentReference2 '[]))
forall a b. (a -> b) -> a -> b
$ \cont :: Ptr (AttachmentReference2 '[]) -> IO b
cont -> SomeStruct AttachmentReference2
-> (forall (es :: [*]).
(Extendss AttachmentReference2 es, PokeChain es) =>
Ptr (AttachmentReference2 es) -> IO b)
-> IO b
forall (a :: [*] -> *) b.
(forall (es :: [*]).
(Extendss a es, PokeChain es) =>
ToCStruct (a es)) =>
SomeStruct a
-> (forall (es :: [*]).
(Extendss a es, PokeChain es) =>
Ptr (a es) -> IO b)
-> IO b
withSomeCStruct @AttachmentReference2 (SomeStruct AttachmentReference2
j) (Ptr (AttachmentReference2 '[]) -> IO b
cont (Ptr (AttachmentReference2 '[]) -> IO b)
-> (Ptr (AttachmentReference2 es)
-> Ptr (AttachmentReference2 '[]))
-> Ptr (AttachmentReference2 es)
-> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr (AttachmentReference2 es) -> Ptr (AttachmentReference2 '[])
forall a b. Ptr a -> Ptr b
castPtr)
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 (AttachmentReference2 '[]))
-> Ptr (AttachmentReference2 '[]) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 es)
-> Int -> Ptr (Ptr (AttachmentReference2 _))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr (Ptr (AttachmentReference2 _)))) Ptr (AttachmentReference2 '[])
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 (SubpassDescription2 es)
p Ptr (SubpassDescription2 es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: 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 (SubpassDescription2 es)
p Ptr (SubpassDescription2 es) -> Int -> Ptr (Ptr Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80 :: 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 = 88
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: Ptr (SubpassDescription2 es) -> IO b -> IO b
pokeZeroCStruct p :: Ptr (SubpassDescription2 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 (SubpassDescription2 es)
p Ptr (SubpassDescription2 es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SUBPASS_DESCRIPTION_2)
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 (SubpassDescription2 es)
p Ptr (SubpassDescription2 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 PipelineBindPoint -> PipelineBindPoint -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 es) -> Int -> Ptr PipelineBindPoint
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr PipelineBindPoint)) (PipelineBindPoint
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 (SubpassDescription2 es)
p Ptr (SubpassDescription2 es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
Ptr (AttachmentReference2 Any)
pPInputAttachments' <- ((Ptr (AttachmentReference2 Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (AttachmentReference2 Any))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (AttachmentReference2 Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (AttachmentReference2 Any)))
-> ((Ptr (AttachmentReference2 Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (AttachmentReference2 Any))
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr (AttachmentReference2 Any) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(AttachmentReference2 _) ((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
* 32) 8
(Int -> SomeStruct AttachmentReference2 -> ContT b IO ())
-> Vector (SomeStruct AttachmentReference2) -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SomeStruct AttachmentReference2
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 (SomeStruct AttachmentReference2)
-> SomeStruct AttachmentReference2 -> IO b -> IO b
forall (a :: [*] -> *) b.
(forall (es :: [*]).
(Extendss a es, PokeChain es) =>
ToCStruct (a es)) =>
Ptr (SomeStruct a) -> SomeStruct a -> IO b -> IO b
pokeSomeCStruct (Ptr (AttachmentReference2 Any)
-> Ptr (SomeStruct AttachmentReference2)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (AttachmentReference2 Any)
pPInputAttachments' Ptr (AttachmentReference2 Any)
-> Int -> Ptr (AttachmentReference2 _)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (32 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (AttachmentReference2 _))) (SomeStruct AttachmentReference2
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 (SomeStruct AttachmentReference2)
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 (AttachmentReference2 Any))
-> Ptr (AttachmentReference2 Any) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 es)
-> Int -> Ptr (Ptr (AttachmentReference2 _))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (Ptr (AttachmentReference2 _)))) (Ptr (AttachmentReference2 Any)
pPInputAttachments')
Ptr (AttachmentReference2 Any)
pPColorAttachments' <- ((Ptr (AttachmentReference2 Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (AttachmentReference2 Any))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (AttachmentReference2 Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (AttachmentReference2 Any)))
-> ((Ptr (AttachmentReference2 Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (AttachmentReference2 Any))
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr (AttachmentReference2 Any) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(AttachmentReference2 _) ((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
* 32) 8
(Int -> SomeStruct AttachmentReference2 -> ContT b IO ())
-> Vector (SomeStruct AttachmentReference2) -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SomeStruct AttachmentReference2
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 (SomeStruct AttachmentReference2)
-> SomeStruct AttachmentReference2 -> IO b -> IO b
forall (a :: [*] -> *) b.
(forall (es :: [*]).
(Extendss a es, PokeChain es) =>
ToCStruct (a es)) =>
Ptr (SomeStruct a) -> SomeStruct a -> IO b -> IO b
pokeSomeCStruct (Ptr (AttachmentReference2 Any)
-> Ptr (SomeStruct AttachmentReference2)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (AttachmentReference2 Any)
pPColorAttachments' Ptr (AttachmentReference2 Any)
-> Int -> Ptr (AttachmentReference2 _)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (32 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (AttachmentReference2 _))) (SomeStruct AttachmentReference2
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 (SomeStruct AttachmentReference2)
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 (AttachmentReference2 Any))
-> Ptr (AttachmentReference2 Any) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 es)
-> Int -> Ptr (Ptr (AttachmentReference2 _))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr (Ptr (AttachmentReference2 _)))) (Ptr (AttachmentReference2 Any)
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 (SubpassDescription2 es)
p Ptr (SubpassDescription2 es) -> Int -> Ptr (Ptr Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80 :: 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 (Extendss SubpassDescription2 es, PeekChain es) => FromCStruct (SubpassDescription2 es) where
peekCStruct :: Ptr (SubpassDescription2 es) -> IO (SubpassDescription2 es)
peekCStruct p :: Ptr (SubpassDescription2 es)
p = do
Ptr ()
pNext <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 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)
SubpassDescriptionFlags
flags <- Ptr SubpassDescriptionFlags -> IO SubpassDescriptionFlags
forall a. Storable a => Ptr a -> IO a
peek @SubpassDescriptionFlags ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 es) -> Int -> Ptr SubpassDescriptionFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr SubpassDescriptionFlags))
PipelineBindPoint
pipelineBindPoint <- Ptr PipelineBindPoint -> IO PipelineBindPoint
forall a. Storable a => Ptr a -> IO a
peek @PipelineBindPoint ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 es) -> Int -> Ptr PipelineBindPoint
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr PipelineBindPoint))
Word32
viewMask <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32))
Word32
inputAttachmentCount <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Word32))
Ptr (AttachmentReference2 Any)
pInputAttachments <- Ptr (Ptr (AttachmentReference2 Any))
-> IO (Ptr (AttachmentReference2 Any))
forall a. Storable a => Ptr a -> IO a
peek @(Ptr (AttachmentReference2 _)) ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 es)
-> Int -> Ptr (Ptr (AttachmentReference2 a))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (Ptr (AttachmentReference2 a))))
Vector (SomeStruct AttachmentReference2)
pInputAttachments' <- Int
-> (Int -> IO (SomeStruct AttachmentReference2))
-> IO (Vector (SomeStruct AttachmentReference2))
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 (SomeStruct AttachmentReference2)
-> IO (SomeStruct AttachmentReference2)
forall (a :: [*] -> *).
(Extensible a,
forall (es :: [*]).
(Extendss a es, PeekChain es) =>
FromCStruct (a es)) =>
Ptr (SomeStruct a) -> IO (SomeStruct a)
peekSomeCStruct (Ptr (AttachmentReference2 Any)
-> Ptr (SomeStruct AttachmentReference2)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions ((Ptr (AttachmentReference2 Any)
pInputAttachments Ptr (AttachmentReference2 Any)
-> Int -> Ptr (AttachmentReference2 Any)
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (32 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (AttachmentReference2 _)))))
Word32
colorAttachmentCount <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Word32))
Ptr (AttachmentReference2 Any)
pColorAttachments <- Ptr (Ptr (AttachmentReference2 Any))
-> IO (Ptr (AttachmentReference2 Any))
forall a. Storable a => Ptr a -> IO a
peek @(Ptr (AttachmentReference2 _)) ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 es)
-> Int -> Ptr (Ptr (AttachmentReference2 a))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr (Ptr (AttachmentReference2 a))))
Vector (SomeStruct AttachmentReference2)
pColorAttachments' <- Int
-> (Int -> IO (SomeStruct AttachmentReference2))
-> IO (Vector (SomeStruct AttachmentReference2))
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 (SomeStruct AttachmentReference2)
-> IO (SomeStruct AttachmentReference2)
forall (a :: [*] -> *).
(Extensible a,
forall (es :: [*]).
(Extendss a es, PeekChain es) =>
FromCStruct (a es)) =>
Ptr (SomeStruct a) -> IO (SomeStruct a)
peekSomeCStruct (Ptr (AttachmentReference2 Any)
-> Ptr (SomeStruct AttachmentReference2)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions ((Ptr (AttachmentReference2 Any)
pColorAttachments Ptr (AttachmentReference2 Any)
-> Int -> Ptr (AttachmentReference2 Any)
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (32 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (AttachmentReference2 _)))))
Ptr (AttachmentReference2 Any)
pResolveAttachments <- Ptr (Ptr (AttachmentReference2 Any))
-> IO (Ptr (AttachmentReference2 Any))
forall a. Storable a => Ptr a -> IO a
peek @(Ptr (AttachmentReference2 _)) ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 es)
-> Int -> Ptr (Ptr (AttachmentReference2 a))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr (Ptr (AttachmentReference2 a))))
let pResolveAttachmentsLength :: Int
pResolveAttachmentsLength = if Ptr (AttachmentReference2 Any)
pResolveAttachments Ptr (AttachmentReference2 Any)
-> Ptr (AttachmentReference2 Any) -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr (AttachmentReference2 Any)
forall a. Ptr a
nullPtr then 0 else (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
colorAttachmentCount)
Vector (SomeStruct AttachmentReference2)
pResolveAttachments' <- Int
-> (Int -> IO (SomeStruct AttachmentReference2))
-> IO (Vector (SomeStruct AttachmentReference2))
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM Int
pResolveAttachmentsLength (\i :: Int
i -> Ptr (SomeStruct AttachmentReference2)
-> IO (SomeStruct AttachmentReference2)
forall (a :: [*] -> *).
(Extensible a,
forall (es :: [*]).
(Extendss a es, PeekChain es) =>
FromCStruct (a es)) =>
Ptr (SomeStruct a) -> IO (SomeStruct a)
peekSomeCStruct (Ptr (AttachmentReference2 Any)
-> Ptr (SomeStruct AttachmentReference2)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions ((Ptr (AttachmentReference2 Any)
pResolveAttachments Ptr (AttachmentReference2 Any)
-> Int -> Ptr (AttachmentReference2 Any)
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (32 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (AttachmentReference2 _)))))
Ptr (AttachmentReference2 Any)
pDepthStencilAttachment <- Ptr (Ptr (AttachmentReference2 Any))
-> IO (Ptr (AttachmentReference2 Any))
forall a. Storable a => Ptr a -> IO a
peek @(Ptr (AttachmentReference2 _)) ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 es)
-> Int -> Ptr (Ptr (AttachmentReference2 a))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr (Ptr (AttachmentReference2 a))))
Maybe (SomeStruct AttachmentReference2)
pDepthStencilAttachment' <- (Ptr (AttachmentReference2 Any)
-> IO (SomeStruct AttachmentReference2))
-> Ptr (AttachmentReference2 Any)
-> IO (Maybe (SomeStruct AttachmentReference2))
forall a b. (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
maybePeek (\j :: Ptr (AttachmentReference2 Any)
j -> Ptr (SomeStruct AttachmentReference2)
-> IO (SomeStruct AttachmentReference2)
forall (a :: [*] -> *).
(Extensible a,
forall (es :: [*]).
(Extendss a es, PeekChain es) =>
FromCStruct (a es)) =>
Ptr (SomeStruct a) -> IO (SomeStruct a)
peekSomeCStruct (Ptr (AttachmentReference2 Any)
-> Ptr (SomeStruct AttachmentReference2)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (AttachmentReference2 Any)
j))) Ptr (AttachmentReference2 Any)
pDepthStencilAttachment
Word32
preserveAttachmentCount <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr Word32))
Ptr Word32
pPreserveAttachments <- Ptr (Ptr Word32) -> IO (Ptr Word32)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr Word32) ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 es) -> Int -> Ptr (Ptr Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80 :: 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)))
SubpassDescription2 es -> IO (SubpassDescription2 es)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SubpassDescription2 es -> IO (SubpassDescription2 es))
-> SubpassDescription2 es -> IO (SubpassDescription2 es)
forall a b. (a -> b) -> a -> b
$ Chain es
-> SubpassDescriptionFlags
-> PipelineBindPoint
-> Word32
-> Vector (SomeStruct AttachmentReference2)
-> Vector (SomeStruct AttachmentReference2)
-> Vector (SomeStruct AttachmentReference2)
-> Maybe (SomeStruct AttachmentReference2)
-> Vector Word32
-> SubpassDescription2 es
forall (es :: [*]).
Chain es
-> SubpassDescriptionFlags
-> PipelineBindPoint
-> Word32
-> Vector (SomeStruct AttachmentReference2)
-> Vector (SomeStruct AttachmentReference2)
-> Vector (SomeStruct AttachmentReference2)
-> Maybe (SomeStruct AttachmentReference2)
-> Vector Word32
-> SubpassDescription2 es
SubpassDescription2
Chain es
next SubpassDescriptionFlags
flags PipelineBindPoint
pipelineBindPoint Word32
viewMask Vector (SomeStruct AttachmentReference2)
pInputAttachments' Vector (SomeStruct AttachmentReference2)
pColorAttachments' Vector (SomeStruct AttachmentReference2)
pResolveAttachments' Maybe (SomeStruct AttachmentReference2)
pDepthStencilAttachment' Vector Word32
pPreserveAttachments'
instance es ~ '[] => Zero (SubpassDescription2 es) where
zero :: SubpassDescription2 es
zero = Chain es
-> SubpassDescriptionFlags
-> PipelineBindPoint
-> Word32
-> Vector (SomeStruct AttachmentReference2)
-> Vector (SomeStruct AttachmentReference2)
-> Vector (SomeStruct AttachmentReference2)
-> Maybe (SomeStruct AttachmentReference2)
-> Vector Word32
-> SubpassDescription2 es
forall (es :: [*]).
Chain es
-> SubpassDescriptionFlags
-> PipelineBindPoint
-> Word32
-> Vector (SomeStruct AttachmentReference2)
-> Vector (SomeStruct AttachmentReference2)
-> Vector (SomeStruct AttachmentReference2)
-> Maybe (SomeStruct AttachmentReference2)
-> Vector Word32
-> SubpassDescription2 es
SubpassDescription2
()
SubpassDescriptionFlags
forall a. Zero a => a
zero
PipelineBindPoint
forall a. Zero a => a
zero
Word32
forall a. Zero a => a
zero
Vector (SomeStruct AttachmentReference2)
forall a. Monoid a => a
mempty
Vector (SomeStruct AttachmentReference2)
forall a. Monoid a => a
mempty
Vector (SomeStruct AttachmentReference2)
forall a. Monoid a => a
mempty
Maybe (SomeStruct AttachmentReference2)
forall a. Maybe a
Nothing
Vector Word32
forall a. Monoid a => a
mempty
data SubpassDependency2 = SubpassDependency2
{
SubpassDependency2 -> Word32
srcSubpass :: Word32
,
SubpassDependency2 -> Word32
dstSubpass :: Word32
,
SubpassDependency2 -> PipelineStageFlags
srcStageMask :: PipelineStageFlags
,
SubpassDependency2 -> PipelineStageFlags
dstStageMask :: PipelineStageFlags
,
SubpassDependency2 -> AccessFlags
srcAccessMask :: AccessFlags
,
SubpassDependency2 -> AccessFlags
dstAccessMask :: AccessFlags
,
SubpassDependency2 -> DependencyFlags
dependencyFlags :: DependencyFlags
,
SubpassDependency2 -> Int32
viewOffset :: Int32
}
deriving (Typeable)
deriving instance Show SubpassDependency2
instance ToCStruct SubpassDependency2 where
withCStruct :: SubpassDependency2 -> (Ptr SubpassDependency2 -> IO b) -> IO b
withCStruct x :: SubpassDependency2
x f :: Ptr SubpassDependency2 -> IO b
f = Int -> Int -> (Ptr SubpassDependency2 -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 48 8 ((Ptr SubpassDependency2 -> IO b) -> IO b)
-> (Ptr SubpassDependency2 -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr SubpassDependency2
p -> Ptr SubpassDependency2 -> SubpassDependency2 -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr SubpassDependency2
p SubpassDependency2
x (Ptr SubpassDependency2 -> IO b
f Ptr SubpassDependency2
p)
pokeCStruct :: Ptr SubpassDependency2 -> SubpassDependency2 -> IO b -> IO b
pokeCStruct p :: Ptr SubpassDependency2
p SubpassDependency2{..} f :: IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SUBPASS_DEPENDENCY_2)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) (Word32
srcSubpass)
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) (Word32
dstSubpass)
Ptr PipelineStageFlags -> PipelineStageFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr PipelineStageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr PipelineStageFlags)) (PipelineStageFlags
srcStageMask)
Ptr PipelineStageFlags -> PipelineStageFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr PipelineStageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr PipelineStageFlags)) (PipelineStageFlags
dstStageMask)
Ptr AccessFlags -> AccessFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr AccessFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr AccessFlags)) (AccessFlags
srcAccessMask)
Ptr AccessFlags -> AccessFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr AccessFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr AccessFlags)) (AccessFlags
dstAccessMask)
Ptr DependencyFlags -> DependencyFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr DependencyFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr DependencyFlags)) (DependencyFlags
dependencyFlags)
Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Int32)) (Int32
viewOffset)
IO b
f
cStructSize :: Int
cStructSize = 48
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: Ptr SubpassDependency2 -> IO b -> IO b
pokeZeroCStruct p :: Ptr SubpassDependency2
p f :: IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SUBPASS_DEPENDENCY_2)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
Ptr PipelineStageFlags -> PipelineStageFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr PipelineStageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr PipelineStageFlags)) (PipelineStageFlags
forall a. Zero a => a
zero)
Ptr PipelineStageFlags -> PipelineStageFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr PipelineStageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr PipelineStageFlags)) (PipelineStageFlags
forall a. Zero a => a
zero)
IO b
f
instance FromCStruct SubpassDependency2 where
peekCStruct :: Ptr SubpassDependency2 -> IO SubpassDependency2
peekCStruct p :: Ptr SubpassDependency2
p = do
Word32
srcSubpass <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32))
Word32
dstSubpass <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32))
PipelineStageFlags
srcStageMask <- Ptr PipelineStageFlags -> IO PipelineStageFlags
forall a. Storable a => Ptr a -> IO a
peek @PipelineStageFlags ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr PipelineStageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr PipelineStageFlags))
PipelineStageFlags
dstStageMask <- Ptr PipelineStageFlags -> IO PipelineStageFlags
forall a. Storable a => Ptr a -> IO a
peek @PipelineStageFlags ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr PipelineStageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr PipelineStageFlags))
AccessFlags
srcAccessMask <- Ptr AccessFlags -> IO AccessFlags
forall a. Storable a => Ptr a -> IO a
peek @AccessFlags ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr AccessFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr AccessFlags))
AccessFlags
dstAccessMask <- Ptr AccessFlags -> IO AccessFlags
forall a. Storable a => Ptr a -> IO a
peek @AccessFlags ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr AccessFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr AccessFlags))
DependencyFlags
dependencyFlags <- Ptr DependencyFlags -> IO DependencyFlags
forall a. Storable a => Ptr a -> IO a
peek @DependencyFlags ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr DependencyFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr DependencyFlags))
Int32
viewOffset <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek @Int32 ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Int32))
SubpassDependency2 -> IO SubpassDependency2
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SubpassDependency2 -> IO SubpassDependency2)
-> SubpassDependency2 -> IO SubpassDependency2
forall a b. (a -> b) -> a -> b
$ Word32
-> Word32
-> PipelineStageFlags
-> PipelineStageFlags
-> AccessFlags
-> AccessFlags
-> DependencyFlags
-> Int32
-> SubpassDependency2
SubpassDependency2
Word32
srcSubpass Word32
dstSubpass PipelineStageFlags
srcStageMask PipelineStageFlags
dstStageMask AccessFlags
srcAccessMask AccessFlags
dstAccessMask DependencyFlags
dependencyFlags Int32
viewOffset
instance Storable SubpassDependency2 where
sizeOf :: SubpassDependency2 -> Int
sizeOf ~SubpassDependency2
_ = 48
alignment :: SubpassDependency2 -> Int
alignment ~SubpassDependency2
_ = 8
peek :: Ptr SubpassDependency2 -> IO SubpassDependency2
peek = Ptr SubpassDependency2 -> IO SubpassDependency2
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr SubpassDependency2 -> SubpassDependency2 -> IO ()
poke ptr :: Ptr SubpassDependency2
ptr poked :: SubpassDependency2
poked = Ptr SubpassDependency2 -> SubpassDependency2 -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr SubpassDependency2
ptr SubpassDependency2
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero SubpassDependency2 where
zero :: SubpassDependency2
zero = Word32
-> Word32
-> PipelineStageFlags
-> PipelineStageFlags
-> AccessFlags
-> AccessFlags
-> DependencyFlags
-> Int32
-> SubpassDependency2
SubpassDependency2
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
Int32
forall a. Zero a => a
zero
data RenderPassCreateInfo2 (es :: [Type]) = RenderPassCreateInfo2
{
RenderPassCreateInfo2 es -> Chain es
next :: Chain es
,
RenderPassCreateInfo2 es -> RenderPassCreateFlags
flags :: RenderPassCreateFlags
,
RenderPassCreateInfo2 es
-> Vector (SomeStruct AttachmentDescription2)
attachments :: Vector (SomeStruct AttachmentDescription2)
,
RenderPassCreateInfo2 es -> Vector (SomeStruct SubpassDescription2)
subpasses :: Vector (SomeStruct SubpassDescription2)
,
RenderPassCreateInfo2 es -> Vector SubpassDependency2
dependencies :: Vector SubpassDependency2
,
RenderPassCreateInfo2 es -> Vector Word32
correlatedViewMasks :: Vector Word32
}
deriving (Typeable)
deriving instance Show (Chain es) => Show (RenderPassCreateInfo2 es)
instance Extensible RenderPassCreateInfo2 where
extensibleType :: StructureType
extensibleType = StructureType
STRUCTURE_TYPE_RENDER_PASS_CREATE_INFO_2
setNext :: RenderPassCreateInfo2 ds -> Chain es -> RenderPassCreateInfo2 es
setNext x :: RenderPassCreateInfo2 ds
x next :: Chain es
next = RenderPassCreateInfo2 ds
x{$sel:next:RenderPassCreateInfo2 :: Chain es
next = Chain es
next}
getNext :: RenderPassCreateInfo2 es -> Chain es
getNext RenderPassCreateInfo2{..} = Chain es
next
extends :: forall e b proxy. Typeable e => proxy e -> (Extends RenderPassCreateInfo2 e => b) -> Maybe b
extends :: proxy e -> (Extends RenderPassCreateInfo2 e => b) -> Maybe b
extends _ f :: Extends RenderPassCreateInfo2 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 RenderPassCreateInfo2 e => b
f
| Bool
otherwise = Maybe b
forall a. Maybe a
Nothing
instance (Extendss RenderPassCreateInfo2 es, PokeChain es) => ToCStruct (RenderPassCreateInfo2 es) where
withCStruct :: RenderPassCreateInfo2 es
-> (Ptr (RenderPassCreateInfo2 es) -> IO b) -> IO b
withCStruct x :: RenderPassCreateInfo2 es
x f :: Ptr (RenderPassCreateInfo2 es) -> IO b
f = Int -> Int -> (Ptr (RenderPassCreateInfo2 es) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 80 8 ((Ptr (RenderPassCreateInfo2 es) -> IO b) -> IO b)
-> (Ptr (RenderPassCreateInfo2 es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr (RenderPassCreateInfo2 es)
p -> Ptr (RenderPassCreateInfo2 es)
-> RenderPassCreateInfo2 es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (RenderPassCreateInfo2 es)
p RenderPassCreateInfo2 es
x (Ptr (RenderPassCreateInfo2 es) -> IO b
f Ptr (RenderPassCreateInfo2 es)
p)
pokeCStruct :: Ptr (RenderPassCreateInfo2 es)
-> RenderPassCreateInfo2 es -> IO b -> IO b
pokeCStruct p :: Ptr (RenderPassCreateInfo2 es)
p RenderPassCreateInfo2{..} 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 (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_RENDER_PASS_CREATE_INFO_2)
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 (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 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 (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 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 (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 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 (SomeStruct AttachmentDescription2) -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector (SomeStruct AttachmentDescription2) -> Int)
-> Vector (SomeStruct AttachmentDescription2) -> Int
forall a b. (a -> b) -> a -> b
$ (Vector (SomeStruct AttachmentDescription2)
attachments)) :: Word32))
Ptr (AttachmentDescription2 Any)
pPAttachments' <- ((Ptr (AttachmentDescription2 Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (AttachmentDescription2 Any))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (AttachmentDescription2 Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (AttachmentDescription2 Any)))
-> ((Ptr (AttachmentDescription2 Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (AttachmentDescription2 Any))
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr (AttachmentDescription2 Any) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(AttachmentDescription2 _) ((Vector (SomeStruct AttachmentDescription2) -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector (SomeStruct AttachmentDescription2)
attachments)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 56) 8
(Int -> SomeStruct AttachmentDescription2 -> ContT b IO ())
-> Vector (SomeStruct AttachmentDescription2) -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SomeStruct AttachmentDescription2
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 (SomeStruct AttachmentDescription2)
-> SomeStruct AttachmentDescription2 -> IO b -> IO b
forall (a :: [*] -> *) b.
(forall (es :: [*]).
(Extendss a es, PokeChain es) =>
ToCStruct (a es)) =>
Ptr (SomeStruct a) -> SomeStruct a -> IO b -> IO b
pokeSomeCStruct (Ptr (AttachmentDescription2 Any)
-> Ptr (SomeStruct AttachmentDescription2)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (AttachmentDescription2 Any)
pPAttachments' Ptr (AttachmentDescription2 Any)
-> Int -> Ptr (AttachmentDescription2 _)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (56 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (AttachmentDescription2 _))) (SomeStruct AttachmentDescription2
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 (SomeStruct AttachmentDescription2)
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 (AttachmentDescription2 Any))
-> Ptr (AttachmentDescription2 Any) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 es)
-> Int -> Ptr (Ptr (AttachmentDescription2 _))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr (AttachmentDescription2 _)))) (Ptr (AttachmentDescription2 Any)
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 (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 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 (SomeStruct SubpassDescription2) -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector (SomeStruct SubpassDescription2) -> Int)
-> Vector (SomeStruct SubpassDescription2) -> Int
forall a b. (a -> b) -> a -> b
$ (Vector (SomeStruct SubpassDescription2)
subpasses)) :: Word32))
Ptr (SubpassDescription2 Any)
pPSubpasses' <- ((Ptr (SubpassDescription2 Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (SubpassDescription2 Any))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (SubpassDescription2 Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (SubpassDescription2 Any)))
-> ((Ptr (SubpassDescription2 Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (SubpassDescription2 Any))
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr (SubpassDescription2 Any) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(SubpassDescription2 _) ((Vector (SomeStruct SubpassDescription2) -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector (SomeStruct SubpassDescription2)
subpasses)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 88) 8
(Int -> SomeStruct SubpassDescription2 -> ContT b IO ())
-> Vector (SomeStruct SubpassDescription2) -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SomeStruct SubpassDescription2
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 (SomeStruct SubpassDescription2)
-> SomeStruct SubpassDescription2 -> IO b -> IO b
forall (a :: [*] -> *) b.
(forall (es :: [*]).
(Extendss a es, PokeChain es) =>
ToCStruct (a es)) =>
Ptr (SomeStruct a) -> SomeStruct a -> IO b -> IO b
pokeSomeCStruct (Ptr (SubpassDescription2 Any)
-> Ptr (SomeStruct SubpassDescription2)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (SubpassDescription2 Any)
pPSubpasses' Ptr (SubpassDescription2 Any) -> Int -> Ptr (SubpassDescription2 _)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (88 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (SubpassDescription2 _))) (SomeStruct SubpassDescription2
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 (SomeStruct SubpassDescription2)
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 (SubpassDescription2 Any))
-> Ptr (SubpassDescription2 Any) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 es)
-> Int -> Ptr (Ptr (SubpassDescription2 _))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr (SubpassDescription2 _)))) (Ptr (SubpassDescription2 Any)
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 (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 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 SubpassDependency2 -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector SubpassDependency2 -> Int)
-> Vector SubpassDependency2 -> Int
forall a b. (a -> b) -> a -> b
$ (Vector SubpassDependency2
dependencies)) :: Word32))
Ptr SubpassDependency2
pPDependencies' <- ((Ptr SubpassDependency2 -> IO b) -> IO b)
-> ContT b IO (Ptr SubpassDependency2)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr SubpassDependency2 -> IO b) -> IO b)
-> ContT b IO (Ptr SubpassDependency2))
-> ((Ptr SubpassDependency2 -> IO b) -> IO b)
-> ContT b IO (Ptr SubpassDependency2)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr SubpassDependency2 -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @SubpassDependency2 ((Vector SubpassDependency2 -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector SubpassDependency2
dependencies)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 48) 8
(Int -> SubpassDependency2 -> ContT b IO ())
-> Vector SubpassDependency2 -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SubpassDependency2
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 SubpassDependency2 -> SubpassDependency2 -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr SubpassDependency2
pPDependencies' Ptr SubpassDependency2 -> Int -> Ptr SubpassDependency2
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (48 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SubpassDependency2) (SubpassDependency2
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 SubpassDependency2
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 SubpassDependency2) -> Ptr SubpassDependency2 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 es)
-> Int -> Ptr (Ptr SubpassDependency2)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr (Ptr SubpassDependency2))) (Ptr SubpassDependency2
pPDependencies')
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 (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr Word32)) ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector Word32 -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Word32 -> Int) -> Vector Word32 -> Int
forall a b. (a -> b) -> a -> b
$ (Vector Word32
correlatedViewMasks)) :: Word32))
Ptr Word32
pPCorrelatedViewMasks' <- ((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
correlatedViewMasks)) 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
pPCorrelatedViewMasks' 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
correlatedViewMasks)
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 (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 es) -> Int -> Ptr (Ptr Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr (Ptr Word32))) (Ptr Word32
pPCorrelatedViewMasks')
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 = 80
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: Ptr (RenderPassCreateInfo2 es) -> IO b -> IO b
pokeZeroCStruct p :: Ptr (RenderPassCreateInfo2 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 (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_RENDER_PASS_CREATE_INFO_2)
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 (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext'
Ptr (AttachmentDescription2 Any)
pPAttachments' <- ((Ptr (AttachmentDescription2 Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (AttachmentDescription2 Any))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (AttachmentDescription2 Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (AttachmentDescription2 Any)))
-> ((Ptr (AttachmentDescription2 Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (AttachmentDescription2 Any))
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr (AttachmentDescription2 Any) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(AttachmentDescription2 _) ((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
* 56) 8
(Int -> SomeStruct AttachmentDescription2 -> ContT b IO ())
-> Vector (SomeStruct AttachmentDescription2) -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SomeStruct AttachmentDescription2
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 (SomeStruct AttachmentDescription2)
-> SomeStruct AttachmentDescription2 -> IO b -> IO b
forall (a :: [*] -> *) b.
(forall (es :: [*]).
(Extendss a es, PokeChain es) =>
ToCStruct (a es)) =>
Ptr (SomeStruct a) -> SomeStruct a -> IO b -> IO b
pokeSomeCStruct (Ptr (AttachmentDescription2 Any)
-> Ptr (SomeStruct AttachmentDescription2)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (AttachmentDescription2 Any)
pPAttachments' Ptr (AttachmentDescription2 Any)
-> Int -> Ptr (AttachmentDescription2 _)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (56 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (AttachmentDescription2 _))) (SomeStruct AttachmentDescription2
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 (SomeStruct AttachmentDescription2)
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 (AttachmentDescription2 Any))
-> Ptr (AttachmentDescription2 Any) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 es)
-> Int -> Ptr (Ptr (AttachmentDescription2 _))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr (AttachmentDescription2 _)))) (Ptr (AttachmentDescription2 Any)
pPAttachments')
Ptr (SubpassDescription2 Any)
pPSubpasses' <- ((Ptr (SubpassDescription2 Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (SubpassDescription2 Any))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (SubpassDescription2 Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (SubpassDescription2 Any)))
-> ((Ptr (SubpassDescription2 Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (SubpassDescription2 Any))
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr (SubpassDescription2 Any) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(SubpassDescription2 _) ((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
* 88) 8
(Int -> SomeStruct SubpassDescription2 -> ContT b IO ())
-> Vector (SomeStruct SubpassDescription2) -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SomeStruct SubpassDescription2
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 (SomeStruct SubpassDescription2)
-> SomeStruct SubpassDescription2 -> IO b -> IO b
forall (a :: [*] -> *) b.
(forall (es :: [*]).
(Extendss a es, PokeChain es) =>
ToCStruct (a es)) =>
Ptr (SomeStruct a) -> SomeStruct a -> IO b -> IO b
pokeSomeCStruct (Ptr (SubpassDescription2 Any)
-> Ptr (SomeStruct SubpassDescription2)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (SubpassDescription2 Any)
pPSubpasses' Ptr (SubpassDescription2 Any) -> Int -> Ptr (SubpassDescription2 _)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (88 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (SubpassDescription2 _))) (SomeStruct SubpassDescription2
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 (SomeStruct SubpassDescription2)
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 (SubpassDescription2 Any))
-> Ptr (SubpassDescription2 Any) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 es)
-> Int -> Ptr (Ptr (SubpassDescription2 _))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr (SubpassDescription2 _)))) (Ptr (SubpassDescription2 Any)
pPSubpasses')
Ptr SubpassDependency2
pPDependencies' <- ((Ptr SubpassDependency2 -> IO b) -> IO b)
-> ContT b IO (Ptr SubpassDependency2)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr SubpassDependency2 -> IO b) -> IO b)
-> ContT b IO (Ptr SubpassDependency2))
-> ((Ptr SubpassDependency2 -> IO b) -> IO b)
-> ContT b IO (Ptr SubpassDependency2)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr SubpassDependency2 -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @SubpassDependency2 ((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
* 48) 8
(Int -> SubpassDependency2 -> ContT b IO ())
-> Vector SubpassDependency2 -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SubpassDependency2
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 SubpassDependency2 -> SubpassDependency2 -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr SubpassDependency2
pPDependencies' Ptr SubpassDependency2 -> Int -> Ptr SubpassDependency2
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (48 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SubpassDependency2) (SubpassDependency2
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 SubpassDependency2
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 SubpassDependency2) -> Ptr SubpassDependency2 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 es)
-> Int -> Ptr (Ptr SubpassDependency2)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr (Ptr SubpassDependency2))) (Ptr SubpassDependency2
pPDependencies')
Ptr Word32
pPCorrelatedViewMasks' <- ((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
pPCorrelatedViewMasks' 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 (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 es) -> Int -> Ptr (Ptr Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr (Ptr Word32))) (Ptr Word32
pPCorrelatedViewMasks')
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 RenderPassCreateInfo2 es, PeekChain es) => FromCStruct (RenderPassCreateInfo2 es) where
peekCStruct :: Ptr (RenderPassCreateInfo2 es) -> IO (RenderPassCreateInfo2 es)
peekCStruct p :: Ptr (RenderPassCreateInfo2 es)
p = do
Ptr ()
pNext <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 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 (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 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 (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32))
Ptr (AttachmentDescription2 Any)
pAttachments <- Ptr (Ptr (AttachmentDescription2 Any))
-> IO (Ptr (AttachmentDescription2 Any))
forall a. Storable a => Ptr a -> IO a
peek @(Ptr (AttachmentDescription2 _)) ((Ptr (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 es)
-> Int -> Ptr (Ptr (AttachmentDescription2 a))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr (AttachmentDescription2 a))))
Vector (SomeStruct AttachmentDescription2)
pAttachments' <- Int
-> (Int -> IO (SomeStruct AttachmentDescription2))
-> IO (Vector (SomeStruct AttachmentDescription2))
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 (SomeStruct AttachmentDescription2)
-> IO (SomeStruct AttachmentDescription2)
forall (a :: [*] -> *).
(Extensible a,
forall (es :: [*]).
(Extendss a es, PeekChain es) =>
FromCStruct (a es)) =>
Ptr (SomeStruct a) -> IO (SomeStruct a)
peekSomeCStruct (Ptr (AttachmentDescription2 Any)
-> Ptr (SomeStruct AttachmentDescription2)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions ((Ptr (AttachmentDescription2 Any)
pAttachments Ptr (AttachmentDescription2 Any)
-> Int -> Ptr (AttachmentDescription2 Any)
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (56 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (AttachmentDescription2 _)))))
Word32
subpassCount <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word32))
Ptr (SubpassDescription2 Any)
pSubpasses <- Ptr (Ptr (SubpassDescription2 Any))
-> IO (Ptr (SubpassDescription2 Any))
forall a. Storable a => Ptr a -> IO a
peek @(Ptr (SubpassDescription2 _)) ((Ptr (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 es)
-> Int -> Ptr (Ptr (SubpassDescription2 a))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr (SubpassDescription2 a))))
Vector (SomeStruct SubpassDescription2)
pSubpasses' <- Int
-> (Int -> IO (SomeStruct SubpassDescription2))
-> IO (Vector (SomeStruct SubpassDescription2))
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 (SomeStruct SubpassDescription2)
-> IO (SomeStruct SubpassDescription2)
forall (a :: [*] -> *).
(Extensible a,
forall (es :: [*]).
(Extendss a es, PeekChain es) =>
FromCStruct (a es)) =>
Ptr (SomeStruct a) -> IO (SomeStruct a)
peekSomeCStruct (Ptr (SubpassDescription2 Any)
-> Ptr (SomeStruct SubpassDescription2)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions ((Ptr (SubpassDescription2 Any)
pSubpasses Ptr (SubpassDescription2 Any)
-> Int -> Ptr (SubpassDescription2 Any)
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (88 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (SubpassDescription2 _)))))
Word32
dependencyCount <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Word32))
Ptr SubpassDependency2
pDependencies <- Ptr (Ptr SubpassDependency2) -> IO (Ptr SubpassDependency2)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr SubpassDependency2) ((Ptr (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 es)
-> Int -> Ptr (Ptr SubpassDependency2)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr (Ptr SubpassDependency2)))
Vector SubpassDependency2
pDependencies' <- Int
-> (Int -> IO SubpassDependency2) -> IO (Vector SubpassDependency2)
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 SubpassDependency2 -> IO SubpassDependency2
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @SubpassDependency2 ((Ptr SubpassDependency2
pDependencies Ptr SubpassDependency2 -> Int -> Ptr SubpassDependency2
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (48 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SubpassDependency2)))
Word32
correlatedViewMaskCount <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr Word32))
Ptr Word32
pCorrelatedViewMasks <- Ptr (Ptr Word32) -> IO (Ptr Word32)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr Word32) ((Ptr (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 es) -> Int -> Ptr (Ptr Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr (Ptr Word32)))
Vector Word32
pCorrelatedViewMasks' <- 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
correlatedViewMaskCount) (\i :: Int
i -> Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr Word32
pCorrelatedViewMasks 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)))
RenderPassCreateInfo2 es -> IO (RenderPassCreateInfo2 es)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (RenderPassCreateInfo2 es -> IO (RenderPassCreateInfo2 es))
-> RenderPassCreateInfo2 es -> IO (RenderPassCreateInfo2 es)
forall a b. (a -> b) -> a -> b
$ Chain es
-> RenderPassCreateFlags
-> Vector (SomeStruct AttachmentDescription2)
-> Vector (SomeStruct SubpassDescription2)
-> Vector SubpassDependency2
-> Vector Word32
-> RenderPassCreateInfo2 es
forall (es :: [*]).
Chain es
-> RenderPassCreateFlags
-> Vector (SomeStruct AttachmentDescription2)
-> Vector (SomeStruct SubpassDescription2)
-> Vector SubpassDependency2
-> Vector Word32
-> RenderPassCreateInfo2 es
RenderPassCreateInfo2
Chain es
next RenderPassCreateFlags
flags Vector (SomeStruct AttachmentDescription2)
pAttachments' Vector (SomeStruct SubpassDescription2)
pSubpasses' Vector SubpassDependency2
pDependencies' Vector Word32
pCorrelatedViewMasks'
instance es ~ '[] => Zero (RenderPassCreateInfo2 es) where
zero :: RenderPassCreateInfo2 es
zero = Chain es
-> RenderPassCreateFlags
-> Vector (SomeStruct AttachmentDescription2)
-> Vector (SomeStruct SubpassDescription2)
-> Vector SubpassDependency2
-> Vector Word32
-> RenderPassCreateInfo2 es
forall (es :: [*]).
Chain es
-> RenderPassCreateFlags
-> Vector (SomeStruct AttachmentDescription2)
-> Vector (SomeStruct SubpassDescription2)
-> Vector SubpassDependency2
-> Vector Word32
-> RenderPassCreateInfo2 es
RenderPassCreateInfo2
()
RenderPassCreateFlags
forall a. Zero a => a
zero
Vector (SomeStruct AttachmentDescription2)
forall a. Monoid a => a
mempty
Vector (SomeStruct SubpassDescription2)
forall a. Monoid a => a
mempty
Vector SubpassDependency2
forall a. Monoid a => a
mempty
Vector Word32
forall a. Monoid a => a
mempty
data SubpassBeginInfo = SubpassBeginInfo
{
SubpassBeginInfo -> SubpassContents
contents :: SubpassContents }
deriving (Typeable)
deriving instance Show SubpassBeginInfo
instance ToCStruct SubpassBeginInfo where
withCStruct :: SubpassBeginInfo
-> (("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo) -> IO b) -> IO b
withCStruct x :: SubpassBeginInfo
x f :: ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo) -> IO b
f = Int
-> Int
-> (("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo) -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo) -> IO b) -> IO b)
-> (("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pSubpassBeginInfo" ::: Ptr SubpassBeginInfo
p -> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> SubpassBeginInfo -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pSubpassBeginInfo" ::: Ptr SubpassBeginInfo
p SubpassBeginInfo
x (("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo) -> IO b
f "pSubpassBeginInfo" ::: Ptr SubpassBeginInfo
p)
pokeCStruct :: ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> SubpassBeginInfo -> IO b -> IO b
pokeCStruct p :: "pSubpassBeginInfo" ::: Ptr SubpassBeginInfo
p SubpassBeginInfo{..} f :: IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo
p ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SUBPASS_BEGIN_INFO)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo
p ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
Ptr SubpassContents -> SubpassContents -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo
p ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> Int -> Ptr SubpassContents
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr SubpassContents)) (SubpassContents
contents)
IO b
f
cStructSize :: Int
cStructSize = 24
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo) -> IO b -> IO b
pokeZeroCStruct p :: "pSubpassBeginInfo" ::: Ptr SubpassBeginInfo
p f :: IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo
p ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SUBPASS_BEGIN_INFO)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo
p ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
Ptr SubpassContents -> SubpassContents -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo
p ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> Int -> Ptr SubpassContents
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr SubpassContents)) (SubpassContents
forall a. Zero a => a
zero)
IO b
f
instance FromCStruct SubpassBeginInfo where
peekCStruct :: ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> IO SubpassBeginInfo
peekCStruct p :: "pSubpassBeginInfo" ::: Ptr SubpassBeginInfo
p = do
SubpassContents
contents <- Ptr SubpassContents -> IO SubpassContents
forall a. Storable a => Ptr a -> IO a
peek @SubpassContents (("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo
p ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> Int -> Ptr SubpassContents
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr SubpassContents))
SubpassBeginInfo -> IO SubpassBeginInfo
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SubpassBeginInfo -> IO SubpassBeginInfo)
-> SubpassBeginInfo -> IO SubpassBeginInfo
forall a b. (a -> b) -> a -> b
$ SubpassContents -> SubpassBeginInfo
SubpassBeginInfo
SubpassContents
contents
instance Storable SubpassBeginInfo where
sizeOf :: SubpassBeginInfo -> Int
sizeOf ~SubpassBeginInfo
_ = 24
alignment :: SubpassBeginInfo -> Int
alignment ~SubpassBeginInfo
_ = 8
peek :: ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> IO SubpassBeginInfo
peek = ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> IO SubpassBeginInfo
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> SubpassBeginInfo -> IO ()
poke ptr :: "pSubpassBeginInfo" ::: Ptr SubpassBeginInfo
ptr poked :: SubpassBeginInfo
poked = ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> SubpassBeginInfo -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pSubpassBeginInfo" ::: Ptr SubpassBeginInfo
ptr SubpassBeginInfo
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero SubpassBeginInfo where
zero :: SubpassBeginInfo
zero = SubpassContents -> SubpassBeginInfo
SubpassBeginInfo
SubpassContents
forall a. Zero a => a
zero
data SubpassEndInfo = SubpassEndInfo
{}
deriving (Typeable)
deriving instance Show SubpassEndInfo
instance ToCStruct SubpassEndInfo where
withCStruct :: SubpassEndInfo
-> (("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO b) -> IO b
withCStruct x :: SubpassEndInfo
x f :: ("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO b
f = Int
-> Int
-> (("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 16 8 ((("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO b) -> IO b)
-> (("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pSubpassEndInfo" ::: Ptr SubpassEndInfo
p -> ("pSubpassEndInfo" ::: Ptr SubpassEndInfo)
-> SubpassEndInfo -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pSubpassEndInfo" ::: Ptr SubpassEndInfo
p SubpassEndInfo
x (("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO b
f "pSubpassEndInfo" ::: Ptr SubpassEndInfo
p)
pokeCStruct :: ("pSubpassEndInfo" ::: Ptr SubpassEndInfo)
-> SubpassEndInfo -> IO b -> IO b
pokeCStruct p :: "pSubpassEndInfo" ::: Ptr SubpassEndInfo
p SubpassEndInfo f :: IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSubpassEndInfo" ::: Ptr SubpassEndInfo
p ("pSubpassEndInfo" ::: Ptr SubpassEndInfo)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SUBPASS_END_INFO)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSubpassEndInfo" ::: Ptr SubpassEndInfo
p ("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
IO b
f
cStructSize :: Int
cStructSize = 16
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: ("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO b -> IO b
pokeZeroCStruct p :: "pSubpassEndInfo" ::: Ptr SubpassEndInfo
p f :: IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSubpassEndInfo" ::: Ptr SubpassEndInfo
p ("pSubpassEndInfo" ::: Ptr SubpassEndInfo)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SUBPASS_END_INFO)
Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSubpassEndInfo" ::: Ptr SubpassEndInfo
p ("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
IO b
f
instance FromCStruct SubpassEndInfo where
peekCStruct :: ("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO SubpassEndInfo
peekCStruct _ = SubpassEndInfo -> IO SubpassEndInfo
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SubpassEndInfo -> IO SubpassEndInfo)
-> SubpassEndInfo -> IO SubpassEndInfo
forall a b. (a -> b) -> a -> b
$ SubpassEndInfo
SubpassEndInfo
instance Storable SubpassEndInfo where
sizeOf :: SubpassEndInfo -> Int
sizeOf ~SubpassEndInfo
_ = 16
alignment :: SubpassEndInfo -> Int
alignment ~SubpassEndInfo
_ = 8
peek :: ("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO SubpassEndInfo
peek = ("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO SubpassEndInfo
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: ("pSubpassEndInfo" ::: Ptr SubpassEndInfo)
-> SubpassEndInfo -> IO ()
poke ptr :: "pSubpassEndInfo" ::: Ptr SubpassEndInfo
ptr poked :: SubpassEndInfo
poked = ("pSubpassEndInfo" ::: Ptr SubpassEndInfo)
-> SubpassEndInfo -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pSubpassEndInfo" ::: Ptr SubpassEndInfo
ptr SubpassEndInfo
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero SubpassEndInfo where
zero :: SubpassEndInfo
zero = SubpassEndInfo
SubpassEndInfo