{-# language CPP #-} -- No documentation found for Chapter "Pass" module Vulkan.Core10.Pass ( createFramebuffer , withFramebuffer , destroyFramebuffer , createRenderPass , withRenderPass , destroyRenderPass , getRenderAreaGranularity , AttachmentDescription(..) , AttachmentReference(..) , SubpassDescription(..) , SubpassDependency(..) , RenderPassCreateInfo(..) , FramebufferCreateInfo(..) , Framebuffer(..) , RenderPass(..) , AttachmentLoadOp(..) , AttachmentStoreOp(..) , PipelineBindPoint(..) , RenderPassCreateFlagBits(..) , RenderPassCreateFlags , AccessFlagBits(..) , AccessFlags , AttachmentDescriptionFlagBits(..) , AttachmentDescriptionFlags , DependencyFlagBits(..) , DependencyFlags , SubpassDescriptionFlagBits(..) , SubpassDescriptionFlags , FramebufferCreateFlagBits(..) , FramebufferCreateFlags ) where import Vulkan.Internal.Utils (traceAroundEvent) import Control.Exception.Base (bracket) import Control.Monad (unless) import Control.Monad.IO.Class (liftIO) import Data.Typeable (eqT) import Foreign.Marshal.Alloc (allocaBytes) import Foreign.Marshal.Alloc (callocBytes) import Foreign.Marshal.Alloc (free) import 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 Vulkan.CStruct (FromCStruct) import Vulkan.CStruct (FromCStruct(..)) import Vulkan.CStruct (ToCStruct) import Vulkan.CStruct (ToCStruct(..)) import Vulkan.Zero (Zero(..)) import Control.Monad.IO.Class (MonadIO) import Data.Type.Equality ((:~:)(Refl)) import Data.Typeable (Typeable) import Foreign.Storable (Storable) import Foreign.Storable (Storable(peek)) import Foreign.Storable (Storable(poke)) import qualified Foreign.Storable (Storable(..)) import GHC.Generics (Generic) import GHC.IO.Exception (IOErrorType(..)) import GHC.IO.Exception (IOException(..)) import Foreign.Ptr (FunPtr) import Foreign.Ptr (Ptr) import 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.NamedType ((:::)) import Vulkan.Core10.Enums.AccessFlagBits (AccessFlags) import Vulkan.Core10.AllocationCallbacks (AllocationCallbacks) import Vulkan.Core10.Enums.AttachmentDescriptionFlagBits (AttachmentDescriptionFlags) import Vulkan.Core10.Enums.AttachmentLoadOp (AttachmentLoadOp) import Vulkan.Core10.Enums.AttachmentStoreOp (AttachmentStoreOp) import Vulkan.CStruct.Extends (Chain) import Vulkan.Core10.Enums.DependencyFlagBits (DependencyFlags) import Vulkan.Core10.Handles (Device) import Vulkan.Core10.Handles (Device(..)) import Vulkan.Core10.Handles (Device(Device)) import Vulkan.Dynamic (DeviceCmds(pVkCreateFramebuffer)) import Vulkan.Dynamic (DeviceCmds(pVkCreateRenderPass)) import Vulkan.Dynamic (DeviceCmds(pVkDestroyFramebuffer)) import Vulkan.Dynamic (DeviceCmds(pVkDestroyRenderPass)) import Vulkan.Dynamic (DeviceCmds(pVkGetRenderAreaGranularity)) import Vulkan.Core10.Handles (Device_T) import Vulkan.CStruct.Extends (Extends) import Vulkan.CStruct.Extends (Extendss) import Vulkan.CStruct.Extends (Extensible(..)) import Vulkan.Core10.FundamentalTypes (Extent2D) import Vulkan.Core10.Enums.Format (Format) import Vulkan.Core10.Handles (Framebuffer) import Vulkan.Core10.Handles (Framebuffer(..)) import {-# SOURCE #-} Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer (FramebufferAttachmentsCreateInfo) import Vulkan.Core10.Enums.FramebufferCreateFlagBits (FramebufferCreateFlags) import Vulkan.Core10.Enums.ImageLayout (ImageLayout) import Vulkan.Core10.Handles (ImageView) import Vulkan.CStruct.Extends (PeekChain) import Vulkan.CStruct.Extends (PeekChain(..)) import Vulkan.Core10.Enums.PipelineBindPoint (PipelineBindPoint) import Vulkan.Core10.Enums.PipelineStageFlagBits (PipelineStageFlags) import Vulkan.CStruct.Extends (PokeChain) import Vulkan.CStruct.Extends (PokeChain(..)) import Vulkan.Core10.Handles (RenderPass) import Vulkan.Core10.Handles (RenderPass(..)) import Vulkan.Core10.Enums.RenderPassCreateFlagBits (RenderPassCreateFlags) import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_fragment_density_map (RenderPassFragmentDensityMapCreateInfoEXT) import {-# SOURCE #-} Vulkan.Core11.Promoted_From_VK_KHR_maintenance2 (RenderPassInputAttachmentAspectCreateInfo) import {-# SOURCE #-} Vulkan.Core11.Promoted_From_VK_KHR_multiview (RenderPassMultiviewCreateInfo) import Vulkan.Core10.Enums.Result (Result) import Vulkan.Core10.Enums.Result (Result(..)) import Vulkan.Core10.Enums.SampleCountFlagBits (SampleCountFlagBits) import Vulkan.CStruct.Extends (SomeStruct) import Vulkan.Core10.Enums.StructureType (StructureType) import Vulkan.Core10.Enums.SubpassDescriptionFlagBits (SubpassDescriptionFlags) import Vulkan.Exception (VulkanException(..)) import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_FRAMEBUFFER_CREATE_INFO)) import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_RENDER_PASS_CREATE_INFO)) import Vulkan.Core10.Enums.Result (Result(SUCCESS)) import Vulkan.Core10.Enums.AccessFlagBits (AccessFlagBits(..)) import Vulkan.Core10.Enums.AccessFlagBits (AccessFlags) import Vulkan.Core10.Enums.AttachmentDescriptionFlagBits (AttachmentDescriptionFlagBits(..)) import Vulkan.Core10.Enums.AttachmentDescriptionFlagBits (AttachmentDescriptionFlags) import Vulkan.Core10.Enums.AttachmentLoadOp (AttachmentLoadOp(..)) import Vulkan.Core10.Enums.AttachmentStoreOp (AttachmentStoreOp(..)) import Vulkan.Core10.Enums.DependencyFlagBits (DependencyFlagBits(..)) import Vulkan.Core10.Enums.DependencyFlagBits (DependencyFlags) import Vulkan.Core10.Handles (Framebuffer(..)) import Vulkan.Core10.Enums.FramebufferCreateFlagBits (FramebufferCreateFlagBits(..)) import Vulkan.Core10.Enums.FramebufferCreateFlagBits (FramebufferCreateFlags) import Vulkan.Core10.Enums.PipelineBindPoint (PipelineBindPoint(..)) import Vulkan.Core10.Handles (RenderPass(..)) import Vulkan.Core10.Enums.RenderPassCreateFlagBits (RenderPassCreateFlagBits(..)) import Vulkan.Core10.Enums.RenderPassCreateFlagBits (RenderPassCreateFlags) import Vulkan.Core10.Enums.SubpassDescriptionFlagBits (SubpassDescriptionFlagBits(..)) import Vulkan.Core10.Enums.SubpassDescriptionFlagBits (SubpassDescriptionFlags) foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCreateFramebuffer :: FunPtr (Ptr Device_T -> Ptr (SomeStruct FramebufferCreateInfo) -> Ptr AllocationCallbacks -> Ptr Framebuffer -> IO Result) -> Ptr Device_T -> Ptr (SomeStruct FramebufferCreateInfo) -> Ptr AllocationCallbacks -> Ptr Framebuffer -> IO Result -- | vkCreateFramebuffer - Create a new framebuffer object -- -- == Valid Usage -- -- - #VUID-vkCreateFramebuffer-pCreateInfo-02777# If @pCreateInfo->flags@ -- does not include -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT', -- and @attachmentCount@ is not @0@, each element of -- @pCreateInfo->pAttachments@ /must/ have been created on @device@ -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCreateFramebuffer-device-parameter# @device@ /must/ be a -- valid 'Vulkan.Core10.Handles.Device' handle -- -- - #VUID-vkCreateFramebuffer-pCreateInfo-parameter# @pCreateInfo@ -- /must/ be a valid pointer to a valid 'FramebufferCreateInfo' -- structure -- -- - #VUID-vkCreateFramebuffer-pAllocator-parameter# If @pAllocator@ is -- not @NULL@, @pAllocator@ /must/ be a valid pointer to a valid -- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' structure -- -- - #VUID-vkCreateFramebuffer-pFramebuffer-parameter# @pFramebuffer@ -- /must/ be a valid pointer to a 'Vulkan.Core10.Handles.Framebuffer' -- handle -- -- == Return Codes -- -- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>] -- -- - 'Vulkan.Core10.Enums.Result.SUCCESS' -- -- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-errorcodes Failure>] -- -- - 'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY' -- -- - 'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_DEVICE_MEMORY' -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks', -- 'Vulkan.Core10.Handles.Device', 'Vulkan.Core10.Handles.Framebuffer', -- 'FramebufferCreateInfo' createFramebuffer :: forall a io . (Extendss FramebufferCreateInfo a, PokeChain a, MonadIO io) => -- | @device@ is the logical device that creates the framebuffer. Device -> -- | @pCreateInfo@ is a pointer to a 'FramebufferCreateInfo' structure -- describing additional information about framebuffer creation. (FramebufferCreateInfo a) -> -- | @pAllocator@ controls host memory allocation as described in the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#memory-allocation Memory Allocation> -- chapter. ("allocator" ::: Maybe AllocationCallbacks) -> io (Framebuffer) createFramebuffer :: forall (a :: [*]) (io :: * -> *). (Extendss FramebufferCreateInfo a, PokeChain a, MonadIO io) => Device -> FramebufferCreateInfo a -> ("allocator" ::: Maybe AllocationCallbacks) -> io Framebuffer createFramebuffer Device device FramebufferCreateInfo a createInfo "allocator" ::: Maybe AllocationCallbacks allocator = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c . forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT forall a b. (a -> b) -> a -> b $ do let vkCreateFramebufferPtr :: FunPtr (Ptr Device_T -> ("pCreateInfo" ::: Ptr (SomeStruct FramebufferCreateInfo)) -> ("pAllocator" ::: Ptr AllocationCallbacks) -> ("pFramebuffer" ::: Ptr Framebuffer) -> IO Result) vkCreateFramebufferPtr = DeviceCmds -> FunPtr (Ptr Device_T -> ("pCreateInfo" ::: Ptr (SomeStruct FramebufferCreateInfo)) -> ("pAllocator" ::: Ptr AllocationCallbacks) -> ("pFramebuffer" ::: Ptr Framebuffer) -> IO Result) pVkCreateFramebuffer (case Device device of Device{DeviceCmds $sel:deviceCmds:Device :: Device -> DeviceCmds deviceCmds :: DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr Device_T -> ("pCreateInfo" ::: Ptr (SomeStruct FramebufferCreateInfo)) -> ("pAllocator" ::: Ptr AllocationCallbacks) -> ("pFramebuffer" ::: Ptr Framebuffer) -> IO Result) vkCreateFramebufferPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCreateFramebuffer is null" forall a. Maybe a Nothing forall a. Maybe a Nothing let vkCreateFramebuffer' :: Ptr Device_T -> ("pCreateInfo" ::: Ptr (SomeStruct FramebufferCreateInfo)) -> ("pAllocator" ::: Ptr AllocationCallbacks) -> ("pFramebuffer" ::: Ptr Framebuffer) -> IO Result vkCreateFramebuffer' = FunPtr (Ptr Device_T -> ("pCreateInfo" ::: Ptr (SomeStruct FramebufferCreateInfo)) -> ("pAllocator" ::: Ptr AllocationCallbacks) -> ("pFramebuffer" ::: Ptr Framebuffer) -> IO Result) -> Ptr Device_T -> ("pCreateInfo" ::: Ptr (SomeStruct FramebufferCreateInfo)) -> ("pAllocator" ::: Ptr AllocationCallbacks) -> ("pFramebuffer" ::: Ptr Framebuffer) -> IO Result mkVkCreateFramebuffer FunPtr (Ptr Device_T -> ("pCreateInfo" ::: Ptr (SomeStruct FramebufferCreateInfo)) -> ("pAllocator" ::: Ptr AllocationCallbacks) -> ("pFramebuffer" ::: Ptr Framebuffer) -> IO Result) vkCreateFramebufferPtr Ptr (FramebufferCreateInfo a) pCreateInfo <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b withCStruct (FramebufferCreateInfo a createInfo) "pAllocator" ::: Ptr AllocationCallbacks pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks allocator) of "allocator" ::: Maybe AllocationCallbacks Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a pure forall a. Ptr a nullPtr Just AllocationCallbacks j -> forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b withCStruct (AllocationCallbacks j) "pFramebuffer" ::: Ptr Framebuffer pPFramebuffer <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c bracket (forall a. Int -> IO (Ptr a) callocBytes @Framebuffer Int 8) forall a. Ptr a -> IO () free Result r <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. String -> IO a -> IO a traceAroundEvent String "vkCreateFramebuffer" (Ptr Device_T -> ("pCreateInfo" ::: Ptr (SomeStruct FramebufferCreateInfo)) -> ("pAllocator" ::: Ptr AllocationCallbacks) -> ("pFramebuffer" ::: Ptr Framebuffer) -> IO Result vkCreateFramebuffer' (Device -> Ptr Device_T deviceHandle (Device device)) (forall (a :: [*] -> *) (es :: [*]). Ptr (a es) -> Ptr (SomeStruct a) forgetExtensions Ptr (FramebufferCreateInfo a) pCreateInfo) "pAllocator" ::: Ptr AllocationCallbacks pAllocator ("pFramebuffer" ::: Ptr Framebuffer pPFramebuffer)) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (f :: * -> *). Applicative f => Bool -> f () -> f () when (Result r forall a. Ord a => a -> a -> Bool < Result SUCCESS) (forall e a. Exception e => e -> IO a throwIO (Result -> VulkanException VulkanException Result r)) Framebuffer pFramebuffer <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> IO a peek @Framebuffer "pFramebuffer" ::: Ptr Framebuffer pPFramebuffer forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ (Framebuffer pFramebuffer) -- | A convenience wrapper to make a compatible pair of calls to -- 'createFramebuffer' and 'destroyFramebuffer' -- -- To ensure that 'destroyFramebuffer' is always called: pass -- 'Control.Exception.bracket' (or the allocate function from your -- favourite resource management library) as the last argument. -- To just extract the pair pass '(,)' as the last argument. -- withFramebuffer :: forall a io r . (Extendss FramebufferCreateInfo a, PokeChain a, MonadIO io) => Device -> FramebufferCreateInfo a -> Maybe AllocationCallbacks -> (io Framebuffer -> (Framebuffer -> io ()) -> r) -> r withFramebuffer :: forall (a :: [*]) (io :: * -> *) r. (Extendss FramebufferCreateInfo a, PokeChain a, MonadIO io) => Device -> FramebufferCreateInfo a -> ("allocator" ::: Maybe AllocationCallbacks) -> (io Framebuffer -> (Framebuffer -> io ()) -> r) -> r withFramebuffer Device device FramebufferCreateInfo a pCreateInfo "allocator" ::: Maybe AllocationCallbacks pAllocator io Framebuffer -> (Framebuffer -> io ()) -> r b = io Framebuffer -> (Framebuffer -> io ()) -> r b (forall (a :: [*]) (io :: * -> *). (Extendss FramebufferCreateInfo a, PokeChain a, MonadIO io) => Device -> FramebufferCreateInfo a -> ("allocator" ::: Maybe AllocationCallbacks) -> io Framebuffer createFramebuffer Device device FramebufferCreateInfo a pCreateInfo "allocator" ::: Maybe AllocationCallbacks pAllocator) (\(Framebuffer o0) -> forall (io :: * -> *). MonadIO io => Device -> Framebuffer -> ("allocator" ::: Maybe AllocationCallbacks) -> io () destroyFramebuffer Device device Framebuffer o0 "allocator" ::: Maybe AllocationCallbacks pAllocator) foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkDestroyFramebuffer :: FunPtr (Ptr Device_T -> Framebuffer -> Ptr AllocationCallbacks -> IO ()) -> Ptr Device_T -> Framebuffer -> Ptr AllocationCallbacks -> IO () -- | vkDestroyFramebuffer - Destroy a framebuffer object -- -- == Valid Usage -- -- - #VUID-vkDestroyFramebuffer-framebuffer-00892# All submitted commands -- that refer to @framebuffer@ /must/ have completed execution -- -- - #VUID-vkDestroyFramebuffer-framebuffer-00893# If -- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' were -- provided when @framebuffer@ was created, a compatible set of -- callbacks /must/ be provided here -- -- - #VUID-vkDestroyFramebuffer-framebuffer-00894# If no -- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' were -- provided when @framebuffer@ was created, @pAllocator@ /must/ be -- @NULL@ -- -- == Valid Usage (Implicit) -- -- - #VUID-vkDestroyFramebuffer-device-parameter# @device@ /must/ be a -- valid 'Vulkan.Core10.Handles.Device' handle -- -- - #VUID-vkDestroyFramebuffer-framebuffer-parameter# If @framebuffer@ -- is not 'Vulkan.Core10.APIConstants.NULL_HANDLE', @framebuffer@ -- /must/ be a valid 'Vulkan.Core10.Handles.Framebuffer' handle -- -- - #VUID-vkDestroyFramebuffer-pAllocator-parameter# If @pAllocator@ is -- not @NULL@, @pAllocator@ /must/ be a valid pointer to a valid -- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' structure -- -- - #VUID-vkDestroyFramebuffer-framebuffer-parent# If @framebuffer@ is a -- valid handle, it /must/ have been created, allocated, or retrieved -- from @device@ -- -- == Host Synchronization -- -- - Host access to @framebuffer@ /must/ be externally synchronized -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks', -- 'Vulkan.Core10.Handles.Device', 'Vulkan.Core10.Handles.Framebuffer' destroyFramebuffer :: forall io . (MonadIO io) => -- | @device@ is the logical device that destroys the framebuffer. Device -> -- | @framebuffer@ is the handle of the framebuffer to destroy. Framebuffer -> -- | @pAllocator@ controls host memory allocation as described in the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#memory-allocation Memory Allocation> -- chapter. ("allocator" ::: Maybe AllocationCallbacks) -> io () destroyFramebuffer :: forall (io :: * -> *). MonadIO io => Device -> Framebuffer -> ("allocator" ::: Maybe AllocationCallbacks) -> io () destroyFramebuffer Device device Framebuffer framebuffer "allocator" ::: Maybe AllocationCallbacks allocator = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c . forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT forall a b. (a -> b) -> a -> b $ do let vkDestroyFramebufferPtr :: FunPtr (Ptr Device_T -> Framebuffer -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) vkDestroyFramebufferPtr = DeviceCmds -> FunPtr (Ptr Device_T -> Framebuffer -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) pVkDestroyFramebuffer (case Device device of Device{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:Device :: Device -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr Device_T -> Framebuffer -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) vkDestroyFramebufferPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkDestroyFramebuffer is null" forall a. Maybe a Nothing forall a. Maybe a Nothing let vkDestroyFramebuffer' :: Ptr Device_T -> Framebuffer -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO () vkDestroyFramebuffer' = FunPtr (Ptr Device_T -> Framebuffer -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> Ptr Device_T -> Framebuffer -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO () mkVkDestroyFramebuffer FunPtr (Ptr Device_T -> Framebuffer -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) vkDestroyFramebufferPtr "pAllocator" ::: Ptr AllocationCallbacks pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks allocator) of "allocator" ::: Maybe AllocationCallbacks Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a pure forall a. Ptr a nullPtr Just AllocationCallbacks j -> forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b withCStruct (AllocationCallbacks j) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. String -> IO a -> IO a traceAroundEvent String "vkDestroyFramebuffer" (Ptr Device_T -> Framebuffer -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO () vkDestroyFramebuffer' (Device -> Ptr Device_T deviceHandle (Device device)) (Framebuffer framebuffer) "pAllocator" ::: Ptr AllocationCallbacks pAllocator) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCreateRenderPass :: FunPtr (Ptr Device_T -> Ptr (SomeStruct RenderPassCreateInfo) -> Ptr AllocationCallbacks -> Ptr RenderPass -> IO Result) -> Ptr Device_T -> Ptr (SomeStruct RenderPassCreateInfo) -> Ptr AllocationCallbacks -> Ptr RenderPass -> IO Result -- | vkCreateRenderPass - Create a new render pass object -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCreateRenderPass-device-parameter# @device@ /must/ be a -- valid 'Vulkan.Core10.Handles.Device' handle -- -- - #VUID-vkCreateRenderPass-pCreateInfo-parameter# @pCreateInfo@ /must/ -- be a valid pointer to a valid 'RenderPassCreateInfo' structure -- -- - #VUID-vkCreateRenderPass-pAllocator-parameter# If @pAllocator@ is -- not @NULL@, @pAllocator@ /must/ be a valid pointer to a valid -- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' structure -- -- - #VUID-vkCreateRenderPass-pRenderPass-parameter# @pRenderPass@ /must/ -- be a valid pointer to a 'Vulkan.Core10.Handles.RenderPass' handle -- -- == Return Codes -- -- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>] -- -- - 'Vulkan.Core10.Enums.Result.SUCCESS' -- -- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-errorcodes Failure>] -- -- - 'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY' -- -- - 'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_DEVICE_MEMORY' -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks', -- 'Vulkan.Core10.Handles.Device', 'Vulkan.Core10.Handles.RenderPass', -- 'RenderPassCreateInfo' createRenderPass :: forall a io . (Extendss RenderPassCreateInfo a, PokeChain a, MonadIO io) => -- | @device@ is the logical device that creates the render pass. Device -> -- | @pCreateInfo@ is a pointer to a 'RenderPassCreateInfo' structure -- describing the parameters of the render pass. (RenderPassCreateInfo a) -> -- | @pAllocator@ controls host memory allocation as described in the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#memory-allocation Memory Allocation> -- chapter. ("allocator" ::: Maybe AllocationCallbacks) -> io (RenderPass) createRenderPass :: forall (a :: [*]) (io :: * -> *). (Extendss RenderPassCreateInfo a, PokeChain a, MonadIO io) => Device -> RenderPassCreateInfo a -> ("allocator" ::: Maybe AllocationCallbacks) -> io RenderPass createRenderPass Device device RenderPassCreateInfo a createInfo "allocator" ::: Maybe AllocationCallbacks allocator = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c . forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT forall a b. (a -> b) -> a -> b $ do let vkCreateRenderPassPtr :: FunPtr (Ptr Device_T -> ("pCreateInfo" ::: Ptr (SomeStruct RenderPassCreateInfo)) -> ("pAllocator" ::: Ptr AllocationCallbacks) -> ("pRenderPass" ::: Ptr RenderPass) -> IO Result) vkCreateRenderPassPtr = DeviceCmds -> FunPtr (Ptr Device_T -> ("pCreateInfo" ::: Ptr (SomeStruct RenderPassCreateInfo)) -> ("pAllocator" ::: Ptr AllocationCallbacks) -> ("pRenderPass" ::: Ptr RenderPass) -> IO Result) pVkCreateRenderPass (case Device device of Device{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:Device :: Device -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr Device_T -> ("pCreateInfo" ::: Ptr (SomeStruct RenderPassCreateInfo)) -> ("pAllocator" ::: Ptr AllocationCallbacks) -> ("pRenderPass" ::: Ptr RenderPass) -> IO Result) vkCreateRenderPassPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCreateRenderPass is null" forall a. Maybe a Nothing forall a. Maybe a Nothing let vkCreateRenderPass' :: Ptr Device_T -> ("pCreateInfo" ::: Ptr (SomeStruct RenderPassCreateInfo)) -> ("pAllocator" ::: Ptr AllocationCallbacks) -> ("pRenderPass" ::: Ptr RenderPass) -> IO Result vkCreateRenderPass' = FunPtr (Ptr Device_T -> ("pCreateInfo" ::: Ptr (SomeStruct RenderPassCreateInfo)) -> ("pAllocator" ::: Ptr AllocationCallbacks) -> ("pRenderPass" ::: Ptr RenderPass) -> IO Result) -> Ptr Device_T -> ("pCreateInfo" ::: Ptr (SomeStruct RenderPassCreateInfo)) -> ("pAllocator" ::: Ptr AllocationCallbacks) -> ("pRenderPass" ::: Ptr RenderPass) -> IO Result mkVkCreateRenderPass FunPtr (Ptr Device_T -> ("pCreateInfo" ::: Ptr (SomeStruct RenderPassCreateInfo)) -> ("pAllocator" ::: Ptr AllocationCallbacks) -> ("pRenderPass" ::: Ptr RenderPass) -> IO Result) vkCreateRenderPassPtr Ptr (RenderPassCreateInfo a) pCreateInfo <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b withCStruct (RenderPassCreateInfo a createInfo) "pAllocator" ::: Ptr AllocationCallbacks pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks allocator) of "allocator" ::: Maybe AllocationCallbacks Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a pure forall a. Ptr a nullPtr Just AllocationCallbacks j -> forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b withCStruct (AllocationCallbacks j) "pRenderPass" ::: Ptr RenderPass pPRenderPass <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c bracket (forall a. Int -> IO (Ptr a) callocBytes @RenderPass Int 8) forall a. Ptr a -> IO () free Result r <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. String -> IO a -> IO a traceAroundEvent String "vkCreateRenderPass" (Ptr Device_T -> ("pCreateInfo" ::: Ptr (SomeStruct RenderPassCreateInfo)) -> ("pAllocator" ::: Ptr AllocationCallbacks) -> ("pRenderPass" ::: Ptr RenderPass) -> IO Result vkCreateRenderPass' (Device -> Ptr Device_T deviceHandle (Device device)) (forall (a :: [*] -> *) (es :: [*]). Ptr (a es) -> Ptr (SomeStruct a) forgetExtensions Ptr (RenderPassCreateInfo a) pCreateInfo) "pAllocator" ::: Ptr AllocationCallbacks pAllocator ("pRenderPass" ::: Ptr RenderPass pPRenderPass)) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (f :: * -> *). Applicative f => Bool -> f () -> f () when (Result r forall a. Ord a => a -> a -> Bool < Result SUCCESS) (forall e a. Exception e => e -> IO a throwIO (Result -> VulkanException VulkanException Result r)) RenderPass pRenderPass <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> IO a peek @RenderPass "pRenderPass" ::: Ptr RenderPass pPRenderPass forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ (RenderPass pRenderPass) -- | A convenience wrapper to make a compatible pair of calls to -- 'createRenderPass' and 'destroyRenderPass' -- -- To ensure that 'destroyRenderPass' is always called: pass -- 'Control.Exception.bracket' (or the allocate function from your -- favourite resource management library) as the last argument. -- To just extract the pair pass '(,)' as the last argument. -- withRenderPass :: forall a io r . (Extendss RenderPassCreateInfo a, PokeChain a, MonadIO io) => Device -> RenderPassCreateInfo a -> Maybe AllocationCallbacks -> (io RenderPass -> (RenderPass -> io ()) -> r) -> r withRenderPass :: forall (a :: [*]) (io :: * -> *) r. (Extendss RenderPassCreateInfo a, PokeChain a, MonadIO io) => Device -> RenderPassCreateInfo a -> ("allocator" ::: Maybe AllocationCallbacks) -> (io RenderPass -> (RenderPass -> io ()) -> r) -> r withRenderPass Device device RenderPassCreateInfo a pCreateInfo "allocator" ::: Maybe AllocationCallbacks pAllocator io RenderPass -> (RenderPass -> io ()) -> r b = io RenderPass -> (RenderPass -> io ()) -> r b (forall (a :: [*]) (io :: * -> *). (Extendss RenderPassCreateInfo a, PokeChain a, MonadIO io) => Device -> RenderPassCreateInfo a -> ("allocator" ::: Maybe AllocationCallbacks) -> io RenderPass createRenderPass Device device RenderPassCreateInfo a pCreateInfo "allocator" ::: Maybe AllocationCallbacks pAllocator) (\(RenderPass o0) -> forall (io :: * -> *). MonadIO io => Device -> RenderPass -> ("allocator" ::: Maybe AllocationCallbacks) -> io () destroyRenderPass Device device RenderPass o0 "allocator" ::: Maybe AllocationCallbacks pAllocator) foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkDestroyRenderPass :: FunPtr (Ptr Device_T -> RenderPass -> Ptr AllocationCallbacks -> IO ()) -> Ptr Device_T -> RenderPass -> Ptr AllocationCallbacks -> IO () -- | vkDestroyRenderPass - Destroy a render pass object -- -- == Valid Usage -- -- - #VUID-vkDestroyRenderPass-renderPass-00873# All submitted commands -- that refer to @renderPass@ /must/ have completed execution -- -- - #VUID-vkDestroyRenderPass-renderPass-00874# If -- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' were -- provided when @renderPass@ was created, a compatible set of -- callbacks /must/ be provided here -- -- - #VUID-vkDestroyRenderPass-renderPass-00875# If no -- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' were -- provided when @renderPass@ was created, @pAllocator@ /must/ be -- @NULL@ -- -- == Valid Usage (Implicit) -- -- - #VUID-vkDestroyRenderPass-device-parameter# @device@ /must/ be a -- valid 'Vulkan.Core10.Handles.Device' handle -- -- - #VUID-vkDestroyRenderPass-renderPass-parameter# If @renderPass@ is -- not 'Vulkan.Core10.APIConstants.NULL_HANDLE', @renderPass@ /must/ be -- a valid 'Vulkan.Core10.Handles.RenderPass' handle -- -- - #VUID-vkDestroyRenderPass-pAllocator-parameter# If @pAllocator@ is -- not @NULL@, @pAllocator@ /must/ be a valid pointer to a valid -- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' structure -- -- - #VUID-vkDestroyRenderPass-renderPass-parent# If @renderPass@ is a -- valid handle, it /must/ have been created, allocated, or retrieved -- from @device@ -- -- == Host Synchronization -- -- - Host access to @renderPass@ /must/ be externally synchronized -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks', -- 'Vulkan.Core10.Handles.Device', 'Vulkan.Core10.Handles.RenderPass' destroyRenderPass :: forall io . (MonadIO io) => -- | @device@ is the logical device that destroys the render pass. Device -> -- | @renderPass@ is the handle of the render pass to destroy. RenderPass -> -- | @pAllocator@ controls host memory allocation as described in the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#memory-allocation Memory Allocation> -- chapter. ("allocator" ::: Maybe AllocationCallbacks) -> io () destroyRenderPass :: forall (io :: * -> *). MonadIO io => Device -> RenderPass -> ("allocator" ::: Maybe AllocationCallbacks) -> io () destroyRenderPass Device device RenderPass renderPass "allocator" ::: Maybe AllocationCallbacks allocator = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c . forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT forall a b. (a -> b) -> a -> b $ do let vkDestroyRenderPassPtr :: FunPtr (Ptr Device_T -> RenderPass -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) vkDestroyRenderPassPtr = DeviceCmds -> FunPtr (Ptr Device_T -> RenderPass -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) pVkDestroyRenderPass (case Device device of Device{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:Device :: Device -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr Device_T -> RenderPass -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) vkDestroyRenderPassPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkDestroyRenderPass is null" forall a. Maybe a Nothing forall a. Maybe a Nothing let vkDestroyRenderPass' :: Ptr Device_T -> RenderPass -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO () vkDestroyRenderPass' = FunPtr (Ptr Device_T -> RenderPass -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> Ptr Device_T -> RenderPass -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO () mkVkDestroyRenderPass FunPtr (Ptr Device_T -> RenderPass -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) vkDestroyRenderPassPtr "pAllocator" ::: Ptr AllocationCallbacks pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks allocator) of "allocator" ::: Maybe AllocationCallbacks Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a pure forall a. Ptr a nullPtr Just AllocationCallbacks j -> forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b withCStruct (AllocationCallbacks j) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. String -> IO a -> IO a traceAroundEvent String "vkDestroyRenderPass" (Ptr Device_T -> RenderPass -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO () vkDestroyRenderPass' (Device -> Ptr Device_T deviceHandle (Device device)) (RenderPass renderPass) "pAllocator" ::: Ptr AllocationCallbacks pAllocator) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkGetRenderAreaGranularity :: FunPtr (Ptr Device_T -> RenderPass -> Ptr Extent2D -> IO ()) -> Ptr Device_T -> RenderPass -> Ptr Extent2D -> IO () -- | vkGetRenderAreaGranularity - Returns the granularity for optimal render -- area -- -- = Description -- -- The conditions leading to an optimal @renderArea@ are: -- -- - the @offset.x@ member in @renderArea@ is a multiple of the @width@ -- member of the returned 'Vulkan.Core10.FundamentalTypes.Extent2D' -- (the horizontal granularity). -- -- - the @offset.y@ member in @renderArea@ is a multiple of the @height@ -- member of the returned 'Vulkan.Core10.FundamentalTypes.Extent2D' -- (the vertical granularity). -- -- - either the @extent.width@ member in @renderArea@ is a multiple of -- the horizontal granularity or @offset.x@+@extent.width@ is equal to -- the @width@ of the @framebuffer@ in the -- 'Vulkan.Core10.CommandBufferBuilding.RenderPassBeginInfo'. -- -- - either the @extent.height@ member in @renderArea@ is a multiple of -- the vertical granularity or @offset.y@+@extent.height@ is equal to -- the @height@ of the @framebuffer@ in the -- 'Vulkan.Core10.CommandBufferBuilding.RenderPassBeginInfo'. -- -- Subpass dependencies are not affected by the render area, and apply to -- the entire image subresources attached to the framebuffer as specified -- in the description of -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#renderpass-layout-transitions automatic layout transitions>. -- Similarly, pipeline barriers are valid even if their effect extends -- outside the render area. -- -- == Valid Usage (Implicit) -- -- - #VUID-vkGetRenderAreaGranularity-device-parameter# @device@ /must/ -- be a valid 'Vulkan.Core10.Handles.Device' handle -- -- - #VUID-vkGetRenderAreaGranularity-renderPass-parameter# @renderPass@ -- /must/ be a valid 'Vulkan.Core10.Handles.RenderPass' handle -- -- - #VUID-vkGetRenderAreaGranularity-pGranularity-parameter# -- @pGranularity@ /must/ be a valid pointer to a -- 'Vulkan.Core10.FundamentalTypes.Extent2D' structure -- -- - #VUID-vkGetRenderAreaGranularity-renderPass-parent# @renderPass@ -- /must/ have been created, allocated, or retrieved from @device@ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- 'Vulkan.Core10.Handles.Device', -- 'Vulkan.Core10.FundamentalTypes.Extent2D', -- 'Vulkan.Core10.Handles.RenderPass' getRenderAreaGranularity :: forall io . (MonadIO io) => -- | @device@ is the logical device that owns the render pass. Device -> -- | @renderPass@ is a handle to a render pass. RenderPass -> io (("granularity" ::: Extent2D)) getRenderAreaGranularity :: forall (io :: * -> *). MonadIO io => Device -> RenderPass -> io ("granularity" ::: Extent2D) getRenderAreaGranularity Device device RenderPass renderPass = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c . forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT forall a b. (a -> b) -> a -> b $ do let vkGetRenderAreaGranularityPtr :: FunPtr (Ptr Device_T -> RenderPass -> ("pGranularity" ::: Ptr ("granularity" ::: Extent2D)) -> IO ()) vkGetRenderAreaGranularityPtr = DeviceCmds -> FunPtr (Ptr Device_T -> RenderPass -> ("pGranularity" ::: Ptr ("granularity" ::: Extent2D)) -> IO ()) pVkGetRenderAreaGranularity (case Device device of Device{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:Device :: Device -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr Device_T -> RenderPass -> ("pGranularity" ::: Ptr ("granularity" ::: Extent2D)) -> IO ()) vkGetRenderAreaGranularityPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkGetRenderAreaGranularity is null" forall a. Maybe a Nothing forall a. Maybe a Nothing let vkGetRenderAreaGranularity' :: Ptr Device_T -> RenderPass -> ("pGranularity" ::: Ptr ("granularity" ::: Extent2D)) -> IO () vkGetRenderAreaGranularity' = FunPtr (Ptr Device_T -> RenderPass -> ("pGranularity" ::: Ptr ("granularity" ::: Extent2D)) -> IO ()) -> Ptr Device_T -> RenderPass -> ("pGranularity" ::: Ptr ("granularity" ::: Extent2D)) -> IO () mkVkGetRenderAreaGranularity FunPtr (Ptr Device_T -> RenderPass -> ("pGranularity" ::: Ptr ("granularity" ::: Extent2D)) -> IO ()) vkGetRenderAreaGranularityPtr "pGranularity" ::: Ptr ("granularity" ::: Extent2D) pPGranularity <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT (forall a b. ToCStruct a => (Ptr a -> IO b) -> IO b withZeroCStruct @Extent2D) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. String -> IO a -> IO a traceAroundEvent String "vkGetRenderAreaGranularity" (Ptr Device_T -> RenderPass -> ("pGranularity" ::: Ptr ("granularity" ::: Extent2D)) -> IO () vkGetRenderAreaGranularity' (Device -> Ptr Device_T deviceHandle (Device device)) (RenderPass renderPass) ("pGranularity" ::: Ptr ("granularity" ::: Extent2D) pPGranularity)) "granularity" ::: Extent2D pGranularity <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. FromCStruct a => Ptr a -> IO a peekCStruct @Extent2D "pGranularity" ::: Ptr ("granularity" ::: Extent2D) pPGranularity forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ ("granularity" ::: Extent2D pGranularity) -- | VkAttachmentDescription - Structure specifying an attachment description -- -- = Description -- -- If the attachment uses a color format, then @loadOp@ and @storeOp@ are -- used, and @stencilLoadOp@ and @stencilStoreOp@ are ignored. If the -- format has depth and\/or stencil components, @loadOp@ and @storeOp@ -- apply only to the depth data, while @stencilLoadOp@ and @stencilStoreOp@ -- define how the stencil data is handled. @loadOp@ and @stencilLoadOp@ -- define the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#renderpass-load-operations load operations> -- for the attachment. @storeOp@ and @stencilStoreOp@ define the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#renderpass-store-operations store operations> -- for the attachment. If an attachment is not used by any subpass, -- @loadOp@, @storeOp@, @stencilStoreOp@, and @stencilLoadOp@ will be -- ignored for that attachment, and no load or store ops will be performed. -- However, any transition specified by @initialLayout@ and @finalLayout@ -- will still be executed. -- -- If @flags@ includes -- 'Vulkan.Core10.Enums.AttachmentDescriptionFlagBits.ATTACHMENT_DESCRIPTION_MAY_ALIAS_BIT', -- then the attachment is treated as if it shares physical memory with -- another attachment in the same render pass. This information limits the -- ability of the implementation to reorder certain operations (like layout -- transitions and the @loadOp@) such that it is not improperly reordered -- against other uses of the same physical memory via a different -- attachment. This is described in more detail below. -- -- If a render pass uses multiple attachments that alias the same device -- memory, those attachments /must/ each include the -- 'Vulkan.Core10.Enums.AttachmentDescriptionFlagBits.ATTACHMENT_DESCRIPTION_MAY_ALIAS_BIT' -- bit in their attachment description flags. Attachments aliasing the same -- memory occurs in multiple ways: -- -- - Multiple attachments being assigned the same image view as part of -- framebuffer creation. -- -- - Attachments using distinct image views that correspond to the same -- image subresource of an image. -- -- - Attachments using views of distinct image subresources which are -- bound to overlapping memory ranges. -- -- Note -- -- Render passes /must/ include subpass dependencies (either directly or -- via a subpass dependency chain) between any two subpasses that operate -- on the same attachment or aliasing attachments and those subpass -- dependencies /must/ include execution and memory dependencies separating -- uses of the aliases, if at least one of those subpasses writes to one of -- the aliases. These dependencies /must/ not include the -- 'Vulkan.Core10.Enums.DependencyFlagBits.DEPENDENCY_BY_REGION_BIT' if the -- aliases are views of distinct image subresources which overlap in -- memory. -- -- Multiple attachments that alias the same memory /must/ not be used in a -- single subpass. A given attachment index /must/ not be used multiple -- times in a single subpass, with one exception: two subpass attachments -- /can/ use the same attachment index if at least one use is as an input -- attachment and neither use is as a resolve or preserve attachment. In -- other words, the same view /can/ be used simultaneously as an input and -- color or depth\/stencil attachment, but /must/ not be used as multiple -- color or depth\/stencil attachments nor as resolve or preserve -- attachments. -- -- If a set of attachments alias each other, then all except the first to -- be used in the render pass /must/ use an @initialLayout@ of -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_UNDEFINED', since the -- earlier uses of the other aliases make their contents undefined. Once an -- alias has been used and a different alias has been used after it, the -- first alias /must/ not be used in any later subpasses. However, an -- application /can/ assign the same image view to multiple aliasing -- attachment indices, which allows that image view to be used multiple -- times even if other aliases are used in between. -- -- Note -- -- Once an attachment needs the -- 'Vulkan.Core10.Enums.AttachmentDescriptionFlagBits.ATTACHMENT_DESCRIPTION_MAY_ALIAS_BIT' -- bit, there /should/ be no additional cost of introducing additional -- aliases, and using these additional aliases /may/ allow more efficient -- clearing of the attachments on multiple uses via -- 'Vulkan.Core10.Enums.AttachmentLoadOp.ATTACHMENT_LOAD_OP_CLEAR'. -- -- == Valid Usage -- -- - #VUID-VkAttachmentDescription-format-06699# If @format@ includes a -- color or depth component and @loadOp@ is -- 'Vulkan.Core10.Enums.AttachmentLoadOp.ATTACHMENT_LOAD_OP_LOAD', then -- @initialLayout@ /must/ not be -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_UNDEFINED' -- -- - #VUID-VkAttachmentDescription-finalLayout-00843# @finalLayout@ -- /must/ not be -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_UNDEFINED' or -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_PREINITIALIZED' -- -- - #VUID-VkAttachmentDescription-format-03280# If @format@ is a color -- format, @initialLayout@ /must/ not be -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_STENCIL_ATTACHMENT_OPTIMAL' -- or -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL' -- -- - #VUID-VkAttachmentDescription-format-03281# If @format@ is a -- depth\/stencil format, @initialLayout@ /must/ not be -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_COLOR_ATTACHMENT_OPTIMAL' -- -- - #VUID-VkAttachmentDescription-format-03282# If @format@ is a color -- format, @finalLayout@ /must/ not be -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_STENCIL_ATTACHMENT_OPTIMAL' -- or -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL' -- -- - #VUID-VkAttachmentDescription-format-03283# If @format@ is a -- depth\/stencil format, @finalLayout@ /must/ not be -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_COLOR_ATTACHMENT_OPTIMAL' -- -- - #VUID-VkAttachmentDescription-format-06487# If @format@ is a color -- format, @initialLayout@ /must/ not be -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_STENCIL_READ_ONLY_OPTIMAL' -- or -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_STENCIL_ATTACHMENT_OPTIMAL' -- -- - #VUID-VkAttachmentDescription-format-06488# If @format@ is a color -- format, @finalLayout@ /must/ not be -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_STENCIL_READ_ONLY_OPTIMAL' -- or -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_STENCIL_ATTACHMENT_OPTIMAL' -- -- - #VUID-VkAttachmentDescription-separateDepthStencilLayouts-03284# If -- the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-separateDepthStencilLayouts separateDepthStencilLayouts> -- feature is not enabled, @initialLayout@ /must/ not be -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL', -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL', -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL', -- or -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL', -- -- - #VUID-VkAttachmentDescription-separateDepthStencilLayouts-03285# If -- the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-separateDepthStencilLayouts separateDepthStencilLayouts> -- feature is not enabled, @finalLayout@ /must/ not be -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL', -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL', -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL', -- or -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL', -- -- - #VUID-VkAttachmentDescription-format-03286# If @format@ is a color -- format, @initialLayout@ /must/ not be -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL', -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL', -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL', -- or -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL' -- -- - #VUID-VkAttachmentDescription-format-03287# If @format@ is a color -- format, @finalLayout@ /must/ not be -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL', -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL', -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL', -- or -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL' -- -- - #VUID-VkAttachmentDescription-format-06906# If @format@ is a -- depth\/stencil format which includes both depth and stencil -- components, @initialLayout@ /must/ not be -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL' -- or -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL' -- -- - #VUID-VkAttachmentDescription-format-06907# If @format@ is a -- depth\/stencil format which includes both depth and stencil -- components, @finalLayout@ /must/ not be -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL' -- or -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL' -- -- - #VUID-VkAttachmentDescription-format-03290# If @format@ is a -- depth\/stencil format which includes only the depth component, -- @initialLayout@ /must/ not be -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL' -- or -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL' -- -- - #VUID-VkAttachmentDescription-format-03291# If @format@ is a -- depth\/stencil format which includes only the depth component, -- @finalLayout@ /must/ not be -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL' -- or -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL' -- -- - #VUID-VkAttachmentDescription-synchronization2-06908# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-synchronization2 synchronization2> -- feature is not enabled, @initialLayout@ /must/ not be -- 'Vulkan.Extensions.VK_KHR_synchronization2.IMAGE_LAYOUT_ATTACHMENT_OPTIMAL_KHR' -- or -- 'Vulkan.Extensions.VK_KHR_synchronization2.IMAGE_LAYOUT_READ_ONLY_OPTIMAL_KHR' -- -- - #VUID-VkAttachmentDescription-synchronization2-06909# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-synchronization2 synchronization2> -- feature is not enabled, @finalLayout@ /must/ not be -- 'Vulkan.Extensions.VK_KHR_synchronization2.IMAGE_LAYOUT_ATTACHMENT_OPTIMAL_KHR' -- or -- 'Vulkan.Extensions.VK_KHR_synchronization2.IMAGE_LAYOUT_READ_ONLY_OPTIMAL_KHR' -- -- - #VUID-VkAttachmentDescription-attachmentFeedbackLoopLayout-07309# If -- the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-attachmentFeedbackLoopLayout attachmentFeedbackLoopLayout> -- feature is not enabled, @initialLayout@ /must/ not be -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_ATTACHMENT_FEEDBACK_LOOP_OPTIMAL_EXT' -- -- - #VUID-VkAttachmentDescription-attachmentFeedbackLoopLayout-07310# If -- the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-attachmentFeedbackLoopLayout attachmentFeedbackLoopLayout> -- feature is not enabled, @finalLayout@ /must/ not be -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_ATTACHMENT_FEEDBACK_LOOP_OPTIMAL_EXT' -- -- - #VUID-VkAttachmentDescription-samples-08745# @samples@ /must/ be a -- bit value that is set in @imageCreateSampleCounts@ (as defined in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-creation-limits Image Creation Limits>) -- for the given @format@ -- -- - #VUID-VkAttachmentDescription-format-06698# @format@ /must/ not be -- VK_FORMAT_UNDEFINED -- -- - #VUID-VkAttachmentDescription-format-06700# If @format@ includes a -- stencil component and @stencilLoadOp@ is -- 'Vulkan.Core10.Enums.AttachmentLoadOp.ATTACHMENT_LOAD_OP_LOAD', then -- @initialLayout@ /must/ not be -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_UNDEFINED' -- -- - #VUID-VkAttachmentDescription-format-03292# If @format@ is a -- depth\/stencil format which includes only the stencil component, -- @initialLayout@ /must/ not be -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL' -- or -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL' -- -- - #VUID-VkAttachmentDescription-format-03293# If @format@ is a -- depth\/stencil format which includes only the stencil component, -- @finalLayout@ /must/ not be -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL' -- or -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL' -- -- - #VUID-VkAttachmentDescription-format-06242# If @format@ is a -- depth\/stencil format which includes both depth and stencil -- components, @initialLayout@ /must/ not be -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL' -- or -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL' -- -- - #VUID-VkAttachmentDescription-format-06243# If @format@ is a -- depth\/stencil format which includes both depth and stencil -- components, @finalLayout@ /must/ not be -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL' -- or -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL' -- -- == Valid Usage (Implicit) -- -- - #VUID-VkAttachmentDescription-flags-parameter# @flags@ /must/ be a -- valid combination of -- 'Vulkan.Core10.Enums.AttachmentDescriptionFlagBits.AttachmentDescriptionFlagBits' -- values -- -- - #VUID-VkAttachmentDescription-format-parameter# @format@ /must/ be a -- valid 'Vulkan.Core10.Enums.Format.Format' value -- -- - #VUID-VkAttachmentDescription-samples-parameter# @samples@ /must/ be -- a valid -- 'Vulkan.Core10.Enums.SampleCountFlagBits.SampleCountFlagBits' value -- -- - #VUID-VkAttachmentDescription-loadOp-parameter# @loadOp@ /must/ be a -- valid 'Vulkan.Core10.Enums.AttachmentLoadOp.AttachmentLoadOp' value -- -- - #VUID-VkAttachmentDescription-storeOp-parameter# @storeOp@ /must/ be -- a valid 'Vulkan.Core10.Enums.AttachmentStoreOp.AttachmentStoreOp' -- value -- -- - #VUID-VkAttachmentDescription-stencilLoadOp-parameter# -- @stencilLoadOp@ /must/ be a valid -- 'Vulkan.Core10.Enums.AttachmentLoadOp.AttachmentLoadOp' value -- -- - #VUID-VkAttachmentDescription-stencilStoreOp-parameter# -- @stencilStoreOp@ /must/ be a valid -- 'Vulkan.Core10.Enums.AttachmentStoreOp.AttachmentStoreOp' value -- -- - #VUID-VkAttachmentDescription-initialLayout-parameter# -- @initialLayout@ /must/ be a valid -- 'Vulkan.Core10.Enums.ImageLayout.ImageLayout' value -- -- - #VUID-VkAttachmentDescription-finalLayout-parameter# @finalLayout@ -- /must/ be a valid 'Vulkan.Core10.Enums.ImageLayout.ImageLayout' -- value -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- 'Vulkan.Core10.Enums.AttachmentDescriptionFlagBits.AttachmentDescriptionFlags', -- 'Vulkan.Core10.Enums.AttachmentLoadOp.AttachmentLoadOp', -- 'Vulkan.Core10.Enums.AttachmentStoreOp.AttachmentStoreOp', -- 'Vulkan.Core10.Enums.Format.Format', -- 'Vulkan.Core10.Enums.ImageLayout.ImageLayout', 'RenderPassCreateInfo', -- 'Vulkan.Core10.Enums.SampleCountFlagBits.SampleCountFlagBits' data AttachmentDescription = AttachmentDescription { -- | @flags@ is a bitmask of -- 'Vulkan.Core10.Enums.AttachmentDescriptionFlagBits.AttachmentDescriptionFlagBits' -- specifying additional properties of the attachment. AttachmentDescription -> AttachmentDescriptionFlags flags :: AttachmentDescriptionFlags , -- | @format@ is a 'Vulkan.Core10.Enums.Format.Format' value specifying the -- format of the image view that will be used for the attachment. AttachmentDescription -> Format format :: Format , -- | @samples@ is a -- 'Vulkan.Core10.Enums.SampleCountFlagBits.SampleCountFlagBits' value -- specifying the number of samples of the image. AttachmentDescription -> SampleCountFlagBits samples :: SampleCountFlagBits , -- | @loadOp@ is a 'Vulkan.Core10.Enums.AttachmentLoadOp.AttachmentLoadOp' -- value specifying how the contents of color and depth components of the -- attachment are treated at the beginning of the subpass where it is first -- used. AttachmentDescription -> AttachmentLoadOp loadOp :: AttachmentLoadOp , -- | @storeOp@ is a 'Vulkan.Core10.Enums.AttachmentStoreOp.AttachmentStoreOp' -- value specifying how the contents of color and depth components of the -- attachment are treated at the end of the subpass where it is last used. AttachmentDescription -> AttachmentStoreOp storeOp :: AttachmentStoreOp , -- | @stencilLoadOp@ is a -- 'Vulkan.Core10.Enums.AttachmentLoadOp.AttachmentLoadOp' value specifying -- how the contents of stencil components of the attachment are treated at -- the beginning of the subpass where it is first used. AttachmentDescription -> AttachmentLoadOp stencilLoadOp :: AttachmentLoadOp , -- | @stencilStoreOp@ is a -- 'Vulkan.Core10.Enums.AttachmentStoreOp.AttachmentStoreOp' value -- specifying how the contents of stencil components of the attachment are -- treated at the end of the last subpass where it is used. AttachmentDescription -> AttachmentStoreOp stencilStoreOp :: AttachmentStoreOp , -- | @initialLayout@ is the layout the attachment image subresource will be -- in when a render pass instance begins. AttachmentDescription -> ImageLayout initialLayout :: ImageLayout , -- | @finalLayout@ is the layout the attachment image subresource will be -- transitioned to when a render pass instance ends. AttachmentDescription -> ImageLayout finalLayout :: ImageLayout } deriving (Typeable, AttachmentDescription -> AttachmentDescription -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: AttachmentDescription -> AttachmentDescription -> Bool $c/= :: AttachmentDescription -> AttachmentDescription -> Bool == :: AttachmentDescription -> AttachmentDescription -> Bool $c== :: AttachmentDescription -> AttachmentDescription -> Bool Eq) #if defined(GENERIC_INSTANCES) deriving instance Generic (AttachmentDescription) #endif deriving instance Show AttachmentDescription instance ToCStruct AttachmentDescription where withCStruct :: forall b. AttachmentDescription -> (Ptr AttachmentDescription -> IO b) -> IO b withCStruct AttachmentDescription x Ptr AttachmentDescription -> IO b f = forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes Int 36 forall a b. (a -> b) -> a -> b $ \Ptr AttachmentDescription p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b pokeCStruct Ptr AttachmentDescription p AttachmentDescription x (Ptr AttachmentDescription -> IO b f Ptr AttachmentDescription p) pokeCStruct :: forall b. Ptr AttachmentDescription -> AttachmentDescription -> IO b -> IO b pokeCStruct Ptr AttachmentDescription p AttachmentDescription{Format ImageLayout SampleCountFlagBits AttachmentStoreOp AttachmentLoadOp AttachmentDescriptionFlags finalLayout :: ImageLayout initialLayout :: ImageLayout stencilStoreOp :: AttachmentStoreOp stencilLoadOp :: AttachmentLoadOp storeOp :: AttachmentStoreOp loadOp :: AttachmentLoadOp samples :: SampleCountFlagBits format :: Format flags :: AttachmentDescriptionFlags $sel:finalLayout:AttachmentDescription :: AttachmentDescription -> ImageLayout $sel:initialLayout:AttachmentDescription :: AttachmentDescription -> ImageLayout $sel:stencilStoreOp:AttachmentDescription :: AttachmentDescription -> AttachmentStoreOp $sel:stencilLoadOp:AttachmentDescription :: AttachmentDescription -> AttachmentLoadOp $sel:storeOp:AttachmentDescription :: AttachmentDescription -> AttachmentStoreOp $sel:loadOp:AttachmentDescription :: AttachmentDescription -> AttachmentLoadOp $sel:samples:AttachmentDescription :: AttachmentDescription -> SampleCountFlagBits $sel:format:AttachmentDescription :: AttachmentDescription -> Format $sel:flags:AttachmentDescription :: AttachmentDescription -> AttachmentDescriptionFlags ..} IO b f = do forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr AttachmentDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr AttachmentDescriptionFlags)) (AttachmentDescriptionFlags flags) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr AttachmentDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 4 :: Ptr Format)) (Format format) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr AttachmentDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr SampleCountFlagBits)) (SampleCountFlagBits samples) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr AttachmentDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 12 :: Ptr AttachmentLoadOp)) (AttachmentLoadOp loadOp) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr AttachmentDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr AttachmentStoreOp)) (AttachmentStoreOp storeOp) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr AttachmentDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 20 :: Ptr AttachmentLoadOp)) (AttachmentLoadOp stencilLoadOp) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr AttachmentDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 24 :: Ptr AttachmentStoreOp)) (AttachmentStoreOp stencilStoreOp) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr AttachmentDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 28 :: Ptr ImageLayout)) (ImageLayout initialLayout) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr AttachmentDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 32 :: Ptr ImageLayout)) (ImageLayout finalLayout) IO b f cStructSize :: Int cStructSize = Int 36 cStructAlignment :: Int cStructAlignment = Int 4 pokeZeroCStruct :: forall b. Ptr AttachmentDescription -> IO b -> IO b pokeZeroCStruct Ptr AttachmentDescription p IO b f = do forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr AttachmentDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 4 :: Ptr Format)) (forall a. Zero a => a zero) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr AttachmentDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr SampleCountFlagBits)) (forall a. Zero a => a zero) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr AttachmentDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 12 :: Ptr AttachmentLoadOp)) (forall a. Zero a => a zero) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr AttachmentDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr AttachmentStoreOp)) (forall a. Zero a => a zero) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr AttachmentDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 20 :: Ptr AttachmentLoadOp)) (forall a. Zero a => a zero) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr AttachmentDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 24 :: Ptr AttachmentStoreOp)) (forall a. Zero a => a zero) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr AttachmentDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 28 :: Ptr ImageLayout)) (forall a. Zero a => a zero) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr AttachmentDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 32 :: Ptr ImageLayout)) (forall a. Zero a => a zero) IO b f instance FromCStruct AttachmentDescription where peekCStruct :: Ptr AttachmentDescription -> IO AttachmentDescription peekCStruct Ptr AttachmentDescription p = do AttachmentDescriptionFlags flags <- forall a. Storable a => Ptr a -> IO a peek @AttachmentDescriptionFlags ((Ptr AttachmentDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr AttachmentDescriptionFlags)) Format format <- forall a. Storable a => Ptr a -> IO a peek @Format ((Ptr AttachmentDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 4 :: Ptr Format)) SampleCountFlagBits samples <- forall a. Storable a => Ptr a -> IO a peek @SampleCountFlagBits ((Ptr AttachmentDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr SampleCountFlagBits)) AttachmentLoadOp loadOp <- forall a. Storable a => Ptr a -> IO a peek @AttachmentLoadOp ((Ptr AttachmentDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 12 :: Ptr AttachmentLoadOp)) AttachmentStoreOp storeOp <- forall a. Storable a => Ptr a -> IO a peek @AttachmentStoreOp ((Ptr AttachmentDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr AttachmentStoreOp)) AttachmentLoadOp stencilLoadOp <- forall a. Storable a => Ptr a -> IO a peek @AttachmentLoadOp ((Ptr AttachmentDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 20 :: Ptr AttachmentLoadOp)) AttachmentStoreOp stencilStoreOp <- forall a. Storable a => Ptr a -> IO a peek @AttachmentStoreOp ((Ptr AttachmentDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 24 :: Ptr AttachmentStoreOp)) ImageLayout initialLayout <- forall a. Storable a => Ptr a -> IO a peek @ImageLayout ((Ptr AttachmentDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 28 :: Ptr ImageLayout)) ImageLayout finalLayout <- forall a. Storable a => Ptr a -> IO a peek @ImageLayout ((Ptr AttachmentDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 32 :: Ptr ImageLayout)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ AttachmentDescriptionFlags -> Format -> SampleCountFlagBits -> AttachmentLoadOp -> AttachmentStoreOp -> AttachmentLoadOp -> AttachmentStoreOp -> ImageLayout -> ImageLayout -> AttachmentDescription AttachmentDescription AttachmentDescriptionFlags flags Format format SampleCountFlagBits samples AttachmentLoadOp loadOp AttachmentStoreOp storeOp AttachmentLoadOp stencilLoadOp AttachmentStoreOp stencilStoreOp ImageLayout initialLayout ImageLayout finalLayout instance Storable AttachmentDescription where sizeOf :: AttachmentDescription -> Int sizeOf ~AttachmentDescription _ = Int 36 alignment :: AttachmentDescription -> Int alignment ~AttachmentDescription _ = Int 4 peek :: Ptr AttachmentDescription -> IO AttachmentDescription peek = forall a. FromCStruct a => Ptr a -> IO a peekCStruct poke :: Ptr AttachmentDescription -> AttachmentDescription -> IO () poke Ptr AttachmentDescription ptr AttachmentDescription poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b pokeCStruct Ptr AttachmentDescription ptr AttachmentDescription poked (forall (f :: * -> *) a. Applicative f => a -> f a pure ()) instance Zero AttachmentDescription where zero :: AttachmentDescription zero = AttachmentDescriptionFlags -> Format -> SampleCountFlagBits -> AttachmentLoadOp -> AttachmentStoreOp -> AttachmentLoadOp -> AttachmentStoreOp -> ImageLayout -> ImageLayout -> AttachmentDescription AttachmentDescription forall a. Zero a => a zero forall a. Zero a => a zero forall a. Zero a => a zero forall a. Zero a => a zero forall a. Zero a => a zero forall a. Zero a => a zero forall a. Zero a => a zero forall a. Zero a => a zero forall a. Zero a => a zero -- | VkAttachmentReference - Structure specifying an attachment reference -- -- == Valid Usage -- -- - #VUID-VkAttachmentReference-layout-03077# If @attachment@ is not -- 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED', @layout@ /must/ not -- be 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_UNDEFINED', -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_PREINITIALIZED', or -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_PRESENT_SRC_KHR' -- -- - #VUID-VkAttachmentReference-separateDepthStencilLayouts-03313# If -- the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-separateDepthStencilLayouts separateDepthStencilLayouts> -- feature is not enabled, and @attachment@ is not -- 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED', @layout@ /must/ not -- be -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL', -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL', -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL', -- or -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL', -- -- - #VUID-VkAttachmentReference-synchronization2-06910# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-synchronization2 synchronization2> -- feature is not enabled, @layout@ /must/ not be -- 'Vulkan.Extensions.VK_KHR_synchronization2.IMAGE_LAYOUT_ATTACHMENT_OPTIMAL_KHR' -- or -- 'Vulkan.Extensions.VK_KHR_synchronization2.IMAGE_LAYOUT_READ_ONLY_OPTIMAL_KHR' -- -- - #VUID-VkAttachmentReference-attachmentFeedbackLoopLayout-07311# If -- the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-attachmentFeedbackLoopLayout attachmentFeedbackLoopLayout> -- feature is not enabled, @layout@ /must/ not be -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_ATTACHMENT_FEEDBACK_LOOP_OPTIMAL_EXT' -- -- == Valid Usage (Implicit) -- -- - #VUID-VkAttachmentReference-layout-parameter# @layout@ /must/ be a -- valid 'Vulkan.Core10.Enums.ImageLayout.ImageLayout' value -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- 'Vulkan.Core10.Enums.ImageLayout.ImageLayout', -- 'Vulkan.Extensions.VK_EXT_fragment_density_map.RenderPassFragmentDensityMapCreateInfoEXT', -- 'SubpassDescription' data AttachmentReference = AttachmentReference { -- | @attachment@ is either an integer value identifying an attachment at the -- corresponding index in 'RenderPassCreateInfo'::@pAttachments@, or -- 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED' to signify that this -- attachment is not used. AttachmentReference -> Word32 attachment :: Word32 , -- | @layout@ is a 'Vulkan.Core10.Enums.ImageLayout.ImageLayout' value -- specifying the layout the attachment uses during the subpass. AttachmentReference -> ImageLayout layout :: ImageLayout } deriving (Typeable, AttachmentReference -> AttachmentReference -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: AttachmentReference -> AttachmentReference -> Bool $c/= :: AttachmentReference -> AttachmentReference -> Bool == :: AttachmentReference -> AttachmentReference -> Bool $c== :: AttachmentReference -> AttachmentReference -> Bool Eq) #if defined(GENERIC_INSTANCES) deriving instance Generic (AttachmentReference) #endif deriving instance Show AttachmentReference instance ToCStruct AttachmentReference where withCStruct :: forall b. AttachmentReference -> (Ptr AttachmentReference -> IO b) -> IO b withCStruct AttachmentReference x Ptr AttachmentReference -> IO b f = forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes Int 8 forall a b. (a -> b) -> a -> b $ \Ptr AttachmentReference p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b pokeCStruct Ptr AttachmentReference p AttachmentReference x (Ptr AttachmentReference -> IO b f Ptr AttachmentReference p) pokeCStruct :: forall b. Ptr AttachmentReference -> AttachmentReference -> IO b -> IO b pokeCStruct Ptr AttachmentReference p AttachmentReference{Word32 ImageLayout layout :: ImageLayout attachment :: Word32 $sel:layout:AttachmentReference :: AttachmentReference -> ImageLayout $sel:attachment:AttachmentReference :: AttachmentReference -> Word32 ..} IO b f = do forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr AttachmentReference p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr Word32)) (Word32 attachment) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr AttachmentReference p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 4 :: Ptr ImageLayout)) (ImageLayout layout) IO b f cStructSize :: Int cStructSize = Int 8 cStructAlignment :: Int cStructAlignment = Int 4 pokeZeroCStruct :: forall b. Ptr AttachmentReference -> IO b -> IO b pokeZeroCStruct Ptr AttachmentReference p IO b f = do forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr AttachmentReference p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr Word32)) (forall a. Zero a => a zero) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr AttachmentReference p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 4 :: Ptr ImageLayout)) (forall a. Zero a => a zero) IO b f instance FromCStruct AttachmentReference where peekCStruct :: Ptr AttachmentReference -> IO AttachmentReference peekCStruct Ptr AttachmentReference p = do Word32 attachment <- forall a. Storable a => Ptr a -> IO a peek @Word32 ((Ptr AttachmentReference p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr Word32)) ImageLayout layout <- forall a. Storable a => Ptr a -> IO a peek @ImageLayout ((Ptr AttachmentReference p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 4 :: Ptr ImageLayout)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ Word32 -> ImageLayout -> AttachmentReference AttachmentReference Word32 attachment ImageLayout layout instance Storable AttachmentReference where sizeOf :: AttachmentReference -> Int sizeOf ~AttachmentReference _ = Int 8 alignment :: AttachmentReference -> Int alignment ~AttachmentReference _ = Int 4 peek :: Ptr AttachmentReference -> IO AttachmentReference peek = forall a. FromCStruct a => Ptr a -> IO a peekCStruct poke :: Ptr AttachmentReference -> AttachmentReference -> IO () poke Ptr AttachmentReference ptr AttachmentReference poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b pokeCStruct Ptr AttachmentReference ptr AttachmentReference poked (forall (f :: * -> *) a. Applicative f => a -> f a pure ()) instance Zero AttachmentReference where zero :: AttachmentReference zero = Word32 -> ImageLayout -> AttachmentReference AttachmentReference forall a. Zero a => a zero forall a. Zero a => a zero -- | VkSubpassDescription - Structure specifying a subpass description -- -- = Description -- -- Each element of the @pInputAttachments@ array corresponds to an input -- attachment index in a fragment shader, i.e. if a shader declares an -- image variable decorated with a @InputAttachmentIndex@ value of __X__, -- then it uses the attachment provided in @pInputAttachments@[__X__]. -- Input attachments /must/ also be bound to the pipeline in a descriptor -- set. If the @attachment@ member of any element of @pInputAttachments@ is -- 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED', the application /must/ -- not read from the corresponding input attachment index. Fragment shaders -- /can/ use subpass input variables to access the contents of an input -- attachment at the fragment’s (x, y, layer) framebuffer coordinates. -- Input attachments /must/ not be used by any subpasses within a render -- pass that enables -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#vertexpostproc-renderpass-transform render pass transform>. -- -- Each element of the @pColorAttachments@ array corresponds to an output -- location in the shader, i.e. if the shader declares an output variable -- decorated with a @Location@ value of __X__, then it uses the attachment -- provided in @pColorAttachments@[__X__]. If the @attachment@ member of -- any element of @pColorAttachments@ is -- 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED', or if -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#framebuffer-color-write-enable Color Write Enable> -- has been disabled for the corresponding attachment index, then writes to -- the corresponding location by a fragment shader are discarded. -- -- If @flags@ does not include -- 'Vulkan.Core10.Enums.SubpassDescriptionFlagBits.SUBPASS_DESCRIPTION_SHADER_RESOLVE_BIT_QCOM', -- and if @pResolveAttachments@ is not @NULL@, each of its elements -- corresponds to a color attachment (the element in @pColorAttachments@ at -- the same index), and a -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#renderpass-resolve-operations multisample resolve operation> -- is defined for each attachment unless the resolve attachment index is -- 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED'. -- -- Similarly, if @flags@ does not include -- 'Vulkan.Core10.Enums.SubpassDescriptionFlagBits.SUBPASS_DESCRIPTION_SHADER_RESOLVE_BIT_QCOM', -- and -- 'Vulkan.Core12.Promoted_From_VK_KHR_depth_stencil_resolve.SubpassDescriptionDepthStencilResolve'::@pDepthStencilResolveAttachment@ -- is not @NULL@ and does not have the value -- 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED', it corresponds to the -- depth\/stencil attachment in @pDepthStencilAttachment@, and -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#renderpass-resolve-operations multisample resolve operation> -- for depth and stencil are defined by -- 'Vulkan.Core12.Promoted_From_VK_KHR_depth_stencil_resolve.SubpassDescriptionDepthStencilResolve'::@depthResolveMode@ -- and -- 'Vulkan.Core12.Promoted_From_VK_KHR_depth_stencil_resolve.SubpassDescriptionDepthStencilResolve'::@stencilResolveMode@, -- respectively. If -- 'Vulkan.Core12.Promoted_From_VK_KHR_depth_stencil_resolve.SubpassDescriptionDepthStencilResolve'::@depthResolveMode@ -- is 'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_NONE' or the -- @pDepthStencilResolveAttachment@ does not have a depth aspect, no -- resolve operation is performed for the depth attachment. If -- 'Vulkan.Core12.Promoted_From_VK_KHR_depth_stencil_resolve.SubpassDescriptionDepthStencilResolve'::@stencilResolveMode@ -- is 'Vulkan.Core12.Enums.ResolveModeFlagBits.RESOLVE_MODE_NONE' or the -- @pDepthStencilResolveAttachment@ does not have a stencil aspect, no -- resolve operation is performed for the stencil attachment. -- -- If the image subresource range referenced by the depth\/stencil -- attachment is created with -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SAMPLE_LOCATIONS_COMPATIBLE_DEPTH_BIT_EXT', -- then the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#renderpass-resolve-operations multisample resolve operation> -- uses the sample locations state specified in the @sampleLocationsInfo@ -- member of the element of the -- 'Vulkan.Extensions.VK_EXT_sample_locations.RenderPassSampleLocationsBeginInfoEXT'::@pPostSubpassSampleLocations@ -- for the subpass. -- -- If @pDepthStencilAttachment@ is @NULL@, or if its attachment index is -- 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED', it indicates that no -- depth\/stencil attachment will be used in the subpass. -- -- The contents of an attachment within the render area become undefined at -- the start of a subpass __S__ if all of the following conditions are -- true: -- -- - The attachment is used as a color, depth\/stencil, or resolve -- attachment in any subpass in the render pass. -- -- - There is a subpass __S1__ that uses or preserves the attachment, and -- a subpass dependency from __S1__ to __S__. -- -- - The attachment is not used or preserved in subpass __S__. -- -- In addition, the contents of an attachment within the render area become -- undefined at the start of a subpass __S__ if all of the following -- conditions are true: -- -- - 'Vulkan.Core10.Enums.SubpassDescriptionFlagBits.SUBPASS_DESCRIPTION_SHADER_RESOLVE_BIT_QCOM' -- is set. -- -- - The attachment is used as a color or depth\/stencil in the subpass. -- -- Once the contents of an attachment become undefined in subpass __S__, -- they remain undefined for subpasses in subpass dependency chains -- starting with subpass __S__ until they are written again. However, they -- remain valid for subpasses in other subpass dependency chains starting -- with subpass __S1__ if those subpasses use or preserve the attachment. -- -- == Valid Usage -- -- - #VUID-VkSubpassDescription-attachment-06912# If the @attachment@ -- member of an element of @pInputAttachments@ is not -- 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED', its @layout@ member -- /must/ not be -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_COLOR_ATTACHMENT_OPTIMAL' -- or -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_STENCIL_ATTACHMENT_OPTIMAL' -- -- - #VUID-VkSubpassDescription-attachment-06913# If the @attachment@ -- member of an element of @pColorAttachments@ is not -- 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED', its @layout@ member -- /must/ not be -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_STENCIL_ATTACHMENT_OPTIMAL' -- or -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_SHADER_READ_ONLY_OPTIMAL' -- -- - #VUID-VkSubpassDescription-attachment-06914# If the @attachment@ -- member of an element of @pResolveAttachments@ is not -- 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED', its @layout@ member -- /must/ not be -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_STENCIL_ATTACHMENT_OPTIMAL' -- or -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_SHADER_READ_ONLY_OPTIMAL' -- -- - #VUID-VkSubpassDescription-attachment-06915# If the @attachment@ -- member of @pDepthStencilAttachment@ is not -- 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED', ts @layout@ member -- /must/ not be -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_COLOR_ATTACHMENT_OPTIMAL' -- or -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_SHADER_READ_ONLY_OPTIMAL' -- -- - #VUID-VkSubpassDescription-attachment-06916# If the @attachment@ -- member of an element of @pColorAttachments@ is not -- 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED', its @layout@ member -- /must/ not be -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_STENCIL_READ_ONLY_OPTIMAL' -- or -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_STENCIL_ATTACHMENT_OPTIMAL' -- -- - #VUID-VkSubpassDescription-attachment-06917# If the @attachment@ -- member of an element of @pResolveAttachments@ is not -- 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED', its @layout@ member -- /must/ not be -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_STENCIL_READ_ONLY_OPTIMAL' -- or -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_STENCIL_ATTACHMENT_OPTIMAL' -- -- - #VUID-VkSubpassDescription-attachment-06918# If the @attachment@ -- member of an element of @pInputAttachments@ is not -- 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED', its @layout@ member -- /must/ not be -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL' -- or -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL' -- -- - #VUID-VkSubpassDescription-attachment-06919# If the @attachment@ -- member of an element of @pColorAttachments@ is not -- 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED', its @layout@ member -- /must/ not be -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL', -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL', -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL', -- or -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL' -- -- - #VUID-VkSubpassDescription-attachment-06920# If the @attachment@ -- member of an element of @pResolveAttachments@ is not -- 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED', its @layout@ member -- /must/ not be -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL', -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL', -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL', -- or -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL' -- -- - #VUID-VkSubpassDescription-attachment-06921# If the @attachment@ -- member of an element of @pInputAttachments@ is not -- 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED', its @layout@ member -- /must/ not be -- 'Vulkan.Extensions.VK_KHR_synchronization2.IMAGE_LAYOUT_ATTACHMENT_OPTIMAL_KHR' -- -- - #VUID-VkSubpassDescription-attachment-06922# If the @attachment@ -- member of an element of @pColorAttachments@ is not -- 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED', its @layout@ member -- /must/ not be -- 'Vulkan.Extensions.VK_KHR_synchronization2.IMAGE_LAYOUT_READ_ONLY_OPTIMAL_KHR' -- -- - #VUID-VkSubpassDescription-attachment-06923# If the @attachment@ -- member of an element of @pResolveAttachments@ is not -- 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED', its @layout@ member -- /must/ not be -- 'Vulkan.Extensions.VK_KHR_synchronization2.IMAGE_LAYOUT_READ_ONLY_OPTIMAL_KHR' -- -- - #VUID-VkSubpassDescription-pipelineBindPoint-04952# -- @pipelineBindPoint@ /must/ be -- 'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_GRAPHICS' -- or -- 'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_SUBPASS_SHADING_HUAWEI' -- -- - #VUID-VkSubpassDescription-colorAttachmentCount-00845# -- @colorAttachmentCount@ /must/ be less than or equal to -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxColorAttachments@ -- -- - #VUID-VkSubpassDescription-loadOp-00846# If the first use of an -- attachment in this render pass is as an input attachment, and the -- attachment is not also used as a color or depth\/stencil attachment -- in the same subpass, then @loadOp@ /must/ not be -- 'Vulkan.Core10.Enums.AttachmentLoadOp.ATTACHMENT_LOAD_OP_CLEAR' -- -- - #VUID-VkSubpassDescription-pResolveAttachments-00847# If -- @pResolveAttachments@ is not @NULL@, for each resolve attachment -- that is not 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED', the -- corresponding color attachment /must/ not be -- 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED' -- -- - #VUID-VkSubpassDescription-pResolveAttachments-00848# If -- @pResolveAttachments@ is not @NULL@, for each resolve attachment -- that is not 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED', the -- corresponding color attachment /must/ not have a sample count of -- 'Vulkan.Core10.Enums.SampleCountFlagBits.SAMPLE_COUNT_1_BIT' -- -- - #VUID-VkSubpassDescription-pResolveAttachments-00849# If -- @pResolveAttachments@ is not @NULL@, each resolve attachment that is -- not 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED' /must/ have a -- sample count of -- 'Vulkan.Core10.Enums.SampleCountFlagBits.SAMPLE_COUNT_1_BIT' -- -- - #VUID-VkSubpassDescription-pResolveAttachments-00850# If -- @pResolveAttachments@ is not @NULL@, each resolve attachment that is -- not 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED' /must/ have the -- same 'Vulkan.Core10.Enums.Format.Format' as its corresponding color -- attachment -- -- - #VUID-VkSubpassDescription-pColorAttachments-06868# If neither the -- @VK_AMD_mixed_attachment_samples@ extension nor the -- @VK_NV_framebuffer_mixed_samples@ extension is enabled, all -- attachments in @pColorAttachments@ that are not -- 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED' /must/ have the same -- sample count -- -- - #VUID-VkSubpassDescription-pInputAttachments-02647# All attachments -- in @pInputAttachments@ that are not -- 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED' /must/ have image -- formats whose -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#potential-format-features potential format features> -- contain at least -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_COLOR_ATTACHMENT_BIT' -- or -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_DEPTH_STENCIL_ATTACHMENT_BIT' -- -- - #VUID-VkSubpassDescription-pColorAttachments-02648# All attachments -- in @pColorAttachments@ that are not -- 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED' /must/ have image -- formats whose -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#potential-format-features potential format features> -- contain -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_COLOR_ATTACHMENT_BIT' -- -- - #VUID-VkSubpassDescription-pResolveAttachments-02649# All -- attachments in @pResolveAttachments@ that are not -- 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED' /must/ have image -- formats whose -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#potential-format-features potential format features> -- contain -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_COLOR_ATTACHMENT_BIT' -- -- - #VUID-VkSubpassDescription-pDepthStencilAttachment-02650# If -- @pDepthStencilAttachment@ is not @NULL@ and the attachment is not -- 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED' then it /must/ have -- an image format whose -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#potential-format-features potential format features> -- contain -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_DEPTH_STENCIL_ATTACHMENT_BIT' -- -- - #VUID-VkSubpassDescription-linearColorAttachment-06496# If the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-linearColorAttachment linearColorAttachment> -- feature is enabled and the image is created with -- 'Vulkan.Core10.Enums.ImageTiling.IMAGE_TILING_LINEAR', all -- attachments in @pInputAttachments@ that are not -- 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED' /must/ have image -- formats whose -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#potential-format-features potential format features> -- /must/ contain -- 'Vulkan.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_LINEAR_COLOR_ATTACHMENT_BIT_NV' -- -- - #VUID-VkSubpassDescription-linearColorAttachment-06497# If the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-linearColorAttachment linearColorAttachment> -- feature is enabled and the image is created with -- 'Vulkan.Core10.Enums.ImageTiling.IMAGE_TILING_LINEAR', all -- attachments in @pColorAttachments@ that are not -- 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED' /must/ have image -- formats whose -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#potential-format-features potential format features> -- /must/ contain -- 'Vulkan.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_LINEAR_COLOR_ATTACHMENT_BIT_NV' -- -- - #VUID-VkSubpassDescription-linearColorAttachment-06498# If the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-linearColorAttachment linearColorAttachment> -- feature is enabled and the image is created with -- 'Vulkan.Core10.Enums.ImageTiling.IMAGE_TILING_LINEAR', all -- attachments in @pResolveAttachments@ that are not -- 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED' /must/ have image -- formats whose -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#potential-format-features potential format features> -- /must/ contain -- 'Vulkan.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_LINEAR_COLOR_ATTACHMENT_BIT_NV' -- -- - #VUID-VkSubpassDescription-pColorAttachments-01506# If the -- @VK_AMD_mixed_attachment_samples@ extension is enabled, all -- attachments in @pColorAttachments@ that are not -- 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED' /must/ have a sample -- count that is smaller than or equal to the sample count of -- @pDepthStencilAttachment@ if it is not -- 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED' -- -- - #VUID-VkSubpassDescription-pDepthStencilAttachment-01418# If neither -- the @VK_AMD_mixed_attachment_samples@ nor the -- @VK_NV_framebuffer_mixed_samples@ extensions are enabled, and if -- @pDepthStencilAttachment@ is not -- 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED' and any attachments -- in @pColorAttachments@ are not -- 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED', they /must/ have the -- same sample count -- -- - #VUID-VkSubpassDescription-attachment-00853# Each element of -- @pPreserveAttachments@ /must/ not be -- 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED' -- -- - #VUID-VkSubpassDescription-pPreserveAttachments-00854# Each element -- of @pPreserveAttachments@ /must/ not also be an element of any other -- member of the subpass description -- -- - #VUID-VkSubpassDescription-layout-02519# If any attachment is used -- by more than one 'AttachmentReference' member, then each use /must/ -- use the same @layout@ -- -- - #VUID-VkSubpassDescription-flags-00856# If @flags@ includes -- 'Vulkan.Core10.Enums.SubpassDescriptionFlagBits.SUBPASS_DESCRIPTION_PER_VIEW_POSITION_X_ONLY_BIT_NVX', -- it /must/ also include -- 'Vulkan.Core10.Enums.SubpassDescriptionFlagBits.SUBPASS_DESCRIPTION_PER_VIEW_ATTRIBUTES_BIT_NVX' -- -- - #VUID-VkSubpassDescription-flags-03341# If @flags@ includes -- 'Vulkan.Core10.Enums.SubpassDescriptionFlagBits.SUBPASS_DESCRIPTION_SHADER_RESOLVE_BIT_QCOM', -- and if @pResolveAttachments@ is not @NULL@, then each resolve -- attachment /must/ be 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED' -- -- - #VUID-VkSubpassDescription-flags-03343# If @flags@ includes -- 'Vulkan.Core10.Enums.SubpassDescriptionFlagBits.SUBPASS_DESCRIPTION_SHADER_RESOLVE_BIT_QCOM', -- then the subpass /must/ be the last subpass in a subpass dependency -- chain -- -- - #VUID-VkSubpassDescription-pInputAttachments-02868# If the render -- pass is created with -- 'Vulkan.Core10.Enums.RenderPassCreateFlagBits.RENDER_PASS_CREATE_TRANSFORM_BIT_QCOM' -- each of the elements of @pInputAttachments@ /must/ be -- 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED' -- -- - #VUID-VkSubpassDescription-pDepthStencilAttachment-04438# -- @pDepthStencilAttachment@ and @pColorAttachments@ must not contain -- references to the same attachment -- -- == Valid Usage (Implicit) -- -- - #VUID-VkSubpassDescription-flags-parameter# @flags@ /must/ be a -- valid combination of -- 'Vulkan.Core10.Enums.SubpassDescriptionFlagBits.SubpassDescriptionFlagBits' -- values -- -- - #VUID-VkSubpassDescription-pipelineBindPoint-parameter# -- @pipelineBindPoint@ /must/ be a valid -- 'Vulkan.Core10.Enums.PipelineBindPoint.PipelineBindPoint' value -- -- - #VUID-VkSubpassDescription-pInputAttachments-parameter# If -- @inputAttachmentCount@ is not @0@, @pInputAttachments@ /must/ be a -- valid pointer to an array of @inputAttachmentCount@ valid -- 'AttachmentReference' structures -- -- - #VUID-VkSubpassDescription-pColorAttachments-parameter# If -- @colorAttachmentCount@ is not @0@, @pColorAttachments@ /must/ be a -- valid pointer to an array of @colorAttachmentCount@ valid -- 'AttachmentReference' structures -- -- - #VUID-VkSubpassDescription-pResolveAttachments-parameter# If -- @colorAttachmentCount@ is not @0@, and @pResolveAttachments@ is not -- @NULL@, @pResolveAttachments@ /must/ be a valid pointer to an array -- of @colorAttachmentCount@ valid 'AttachmentReference' structures -- -- - #VUID-VkSubpassDescription-pDepthStencilAttachment-parameter# If -- @pDepthStencilAttachment@ is not @NULL@, @pDepthStencilAttachment@ -- /must/ be a valid pointer to a valid 'AttachmentReference' structure -- -- - #VUID-VkSubpassDescription-pPreserveAttachments-parameter# If -- @preserveAttachmentCount@ is not @0@, @pPreserveAttachments@ /must/ -- be a valid pointer to an array of @preserveAttachmentCount@ -- @uint32_t@ values -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- 'AttachmentReference', -- 'Vulkan.Core10.Enums.PipelineBindPoint.PipelineBindPoint', -- 'RenderPassCreateInfo', -- 'Vulkan.Core10.Enums.SubpassDescriptionFlagBits.SubpassDescriptionFlags' data SubpassDescription = SubpassDescription { -- | @flags@ is a bitmask of -- 'Vulkan.Core10.Enums.SubpassDescriptionFlagBits.SubpassDescriptionFlagBits' -- specifying usage of the subpass. SubpassDescription -> SubpassDescriptionFlags flags :: SubpassDescriptionFlags , -- | @pipelineBindPoint@ is a -- 'Vulkan.Core10.Enums.PipelineBindPoint.PipelineBindPoint' value -- specifying the pipeline type supported for this subpass. SubpassDescription -> PipelineBindPoint pipelineBindPoint :: PipelineBindPoint , -- | @pInputAttachments@ is a pointer to an array of 'AttachmentReference' -- structures defining the input attachments for this subpass and their -- layouts. SubpassDescription -> Vector AttachmentReference inputAttachments :: Vector AttachmentReference , -- | @pColorAttachments@ is a pointer to an array of @colorAttachmentCount@ -- 'AttachmentReference' structures defining the color attachments for this -- subpass and their layouts. SubpassDescription -> Vector AttachmentReference colorAttachments :: Vector AttachmentReference , -- | @pResolveAttachments@ is @NULL@ or a pointer to an array of -- @colorAttachmentCount@ 'AttachmentReference' structures defining the -- resolve attachments for this subpass and their layouts. SubpassDescription -> Vector AttachmentReference resolveAttachments :: Vector AttachmentReference , -- | @pDepthStencilAttachment@ is a pointer to a 'AttachmentReference' -- structure specifying the depth\/stencil attachment for this subpass and -- its layout. SubpassDescription -> Maybe AttachmentReference depthStencilAttachment :: Maybe AttachmentReference , -- | @pPreserveAttachments@ is a pointer to an array of -- @preserveAttachmentCount@ render pass attachment indices identifying -- attachments that are not used by this subpass, but whose contents /must/ -- be preserved throughout the subpass. SubpassDescription -> Vector Word32 preserveAttachments :: Vector Word32 } deriving (Typeable) #if defined(GENERIC_INSTANCES) deriving instance Generic (SubpassDescription) #endif deriving instance Show SubpassDescription instance ToCStruct SubpassDescription where withCStruct :: forall b. SubpassDescription -> (Ptr SubpassDescription -> IO b) -> IO b withCStruct SubpassDescription x Ptr SubpassDescription -> IO b f = forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes Int 72 forall a b. (a -> b) -> a -> b $ \Ptr SubpassDescription p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b pokeCStruct Ptr SubpassDescription p SubpassDescription x (Ptr SubpassDescription -> IO b f Ptr SubpassDescription p) pokeCStruct :: forall b. Ptr SubpassDescription -> SubpassDescription -> IO b -> IO b pokeCStruct Ptr SubpassDescription p SubpassDescription{Maybe AttachmentReference Vector Word32 Vector AttachmentReference PipelineBindPoint SubpassDescriptionFlags preserveAttachments :: Vector Word32 depthStencilAttachment :: Maybe AttachmentReference resolveAttachments :: Vector AttachmentReference colorAttachments :: Vector AttachmentReference inputAttachments :: Vector AttachmentReference pipelineBindPoint :: PipelineBindPoint flags :: SubpassDescriptionFlags $sel:preserveAttachments:SubpassDescription :: SubpassDescription -> Vector Word32 $sel:depthStencilAttachment:SubpassDescription :: SubpassDescription -> Maybe AttachmentReference $sel:resolveAttachments:SubpassDescription :: SubpassDescription -> Vector AttachmentReference $sel:colorAttachments:SubpassDescription :: SubpassDescription -> Vector AttachmentReference $sel:inputAttachments:SubpassDescription :: SubpassDescription -> Vector AttachmentReference $sel:pipelineBindPoint:SubpassDescription :: SubpassDescription -> PipelineBindPoint $sel:flags:SubpassDescription :: SubpassDescription -> SubpassDescriptionFlags ..} IO b f = forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT forall a b. (a -> b) -> a -> b $ do forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr SubpassDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr SubpassDescriptionFlags)) (SubpassDescriptionFlags flags) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr SubpassDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 4 :: Ptr PipelineBindPoint)) (PipelineBindPoint pipelineBindPoint) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr SubpassDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr Word32)) ((forall a b. (Integral a, Num b) => a -> b fromIntegral (forall a. Vector a -> Int Data.Vector.length forall a b. (a -> b) -> a -> b $ (Vector AttachmentReference inputAttachments)) :: Word32)) Ptr AttachmentReference pPInputAttachments' <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes @AttachmentReference ((forall a. Vector a -> Int Data.Vector.length (Vector AttachmentReference inputAttachments)) forall a. Num a => a -> a -> a * Int 8) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\Int i AttachmentReference e -> forall a. Storable a => Ptr a -> a -> IO () poke (Ptr AttachmentReference pPInputAttachments' forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 8 forall a. Num a => a -> a -> a * (Int i)) :: Ptr AttachmentReference) (AttachmentReference e)) (Vector AttachmentReference inputAttachments) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr SubpassDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr (Ptr AttachmentReference))) (Ptr AttachmentReference pPInputAttachments') let pColorAttachmentsLength :: Int pColorAttachmentsLength = forall a. Vector a -> Int Data.Vector.length forall a b. (a -> b) -> a -> b $ (Vector AttachmentReference colorAttachments) let pResolveAttachmentsLength :: Int pResolveAttachmentsLength = forall a. Vector a -> Int Data.Vector.length forall a b. (a -> b) -> a -> b $ (Vector AttachmentReference resolveAttachments) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (forall a b. (Integral a, Num b) => a -> b fromIntegral Int pResolveAttachmentsLength forall a. Eq a => a -> a -> Bool == Int pColorAttachmentsLength Bool -> Bool -> Bool || Int pResolveAttachmentsLength forall a. Eq a => a -> a -> Bool == Int 0) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "pResolveAttachments and pColorAttachments must have the same length" forall a. Maybe a Nothing forall a. Maybe a Nothing forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr SubpassDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 24 :: Ptr Word32)) ((forall a b. (Integral a, Num b) => a -> b fromIntegral Int pColorAttachmentsLength :: Word32)) Ptr AttachmentReference pPColorAttachments' <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes @AttachmentReference ((forall a. Vector a -> Int Data.Vector.length (Vector AttachmentReference colorAttachments)) forall a. Num a => a -> a -> a * Int 8) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\Int i AttachmentReference e -> forall a. Storable a => Ptr a -> a -> IO () poke (Ptr AttachmentReference pPColorAttachments' forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 8 forall a. Num a => a -> a -> a * (Int i)) :: Ptr AttachmentReference) (AttachmentReference e)) (Vector AttachmentReference colorAttachments) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr SubpassDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 32 :: Ptr (Ptr AttachmentReference))) (Ptr AttachmentReference pPColorAttachments') Ptr AttachmentReference pResolveAttachments'' <- if forall a. Vector a -> Bool Data.Vector.null (Vector AttachmentReference resolveAttachments) then forall (f :: * -> *) a. Applicative f => a -> f a pure forall a. Ptr a nullPtr else do Ptr AttachmentReference pPResolveAttachments <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes @AttachmentReference (((forall a. Vector a -> Int Data.Vector.length (Vector AttachmentReference resolveAttachments))) forall a. Num a => a -> a -> a * Int 8) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\Int i AttachmentReference e -> forall a. Storable a => Ptr a -> a -> IO () poke (Ptr AttachmentReference pPResolveAttachments forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 8 forall a. Num a => a -> a -> a * (Int i)) :: Ptr AttachmentReference) (AttachmentReference e)) ((Vector AttachmentReference resolveAttachments)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ Ptr AttachmentReference pPResolveAttachments forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr SubpassDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 40 :: Ptr (Ptr AttachmentReference))) Ptr AttachmentReference pResolveAttachments'' Ptr AttachmentReference pDepthStencilAttachment'' <- case (Maybe AttachmentReference depthStencilAttachment) of Maybe AttachmentReference Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a pure forall a. Ptr a nullPtr Just AttachmentReference j -> forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b withCStruct (AttachmentReference j) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr SubpassDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 48 :: Ptr (Ptr AttachmentReference))) Ptr AttachmentReference pDepthStencilAttachment'' forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr SubpassDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 56 :: Ptr Word32)) ((forall a b. (Integral a, Num b) => a -> b fromIntegral (forall a. Vector a -> Int Data.Vector.length forall a b. (a -> b) -> a -> b $ (Vector Word32 preserveAttachments)) :: Word32)) Ptr Word32 pPPreserveAttachments' <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes @Word32 ((forall a. Vector a -> Int Data.Vector.length (Vector Word32 preserveAttachments)) forall a. Num a => a -> a -> a * Int 4) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\Int i Word32 e -> forall a. Storable a => Ptr a -> a -> IO () poke (Ptr Word32 pPPreserveAttachments' forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 4 forall a. Num a => a -> a -> a * (Int i)) :: Ptr Word32) (Word32 e)) (Vector Word32 preserveAttachments) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr SubpassDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 64 :: Ptr (Ptr Word32))) (Ptr Word32 pPPreserveAttachments') forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ IO b f cStructSize :: Int cStructSize = Int 72 cStructAlignment :: Int cStructAlignment = Int 8 pokeZeroCStruct :: forall b. Ptr SubpassDescription -> IO b -> IO b pokeZeroCStruct Ptr SubpassDescription p IO b f = do forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr SubpassDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 4 :: Ptr PipelineBindPoint)) (forall a. Zero a => a zero) IO b f instance FromCStruct SubpassDescription where peekCStruct :: Ptr SubpassDescription -> IO SubpassDescription peekCStruct Ptr SubpassDescription p = do SubpassDescriptionFlags flags <- forall a. Storable a => Ptr a -> IO a peek @SubpassDescriptionFlags ((Ptr SubpassDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr SubpassDescriptionFlags)) PipelineBindPoint pipelineBindPoint <- forall a. Storable a => Ptr a -> IO a peek @PipelineBindPoint ((Ptr SubpassDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 4 :: Ptr PipelineBindPoint)) Word32 inputAttachmentCount <- forall a. Storable a => Ptr a -> IO a peek @Word32 ((Ptr SubpassDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr Word32)) Ptr AttachmentReference pInputAttachments <- forall a. Storable a => Ptr a -> IO a peek @(Ptr AttachmentReference) ((Ptr SubpassDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr (Ptr AttachmentReference))) Vector AttachmentReference pInputAttachments' <- forall (m :: * -> *) a. Monad m => Int -> (Int -> m a) -> m (Vector a) generateM (forall a b. (Integral a, Num b) => a -> b fromIntegral Word32 inputAttachmentCount) (\Int i -> forall a. FromCStruct a => Ptr a -> IO a peekCStruct @AttachmentReference ((Ptr AttachmentReference pInputAttachments forall a. Ptr a -> Int -> Ptr a `advancePtrBytes` (Int 8 forall a. Num a => a -> a -> a * (Int i)) :: Ptr AttachmentReference))) Word32 colorAttachmentCount <- forall a. Storable a => Ptr a -> IO a peek @Word32 ((Ptr SubpassDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 24 :: Ptr Word32)) Ptr AttachmentReference pColorAttachments <- forall a. Storable a => Ptr a -> IO a peek @(Ptr AttachmentReference) ((Ptr SubpassDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 32 :: Ptr (Ptr AttachmentReference))) Vector AttachmentReference pColorAttachments' <- forall (m :: * -> *) a. Monad m => Int -> (Int -> m a) -> m (Vector a) generateM (forall a b. (Integral a, Num b) => a -> b fromIntegral Word32 colorAttachmentCount) (\Int i -> forall a. FromCStruct a => Ptr a -> IO a peekCStruct @AttachmentReference ((Ptr AttachmentReference pColorAttachments forall a. Ptr a -> Int -> Ptr a `advancePtrBytes` (Int 8 forall a. Num a => a -> a -> a * (Int i)) :: Ptr AttachmentReference))) Ptr AttachmentReference pResolveAttachments <- forall a. Storable a => Ptr a -> IO a peek @(Ptr AttachmentReference) ((Ptr SubpassDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 40 :: Ptr (Ptr AttachmentReference))) let pResolveAttachmentsLength :: Int pResolveAttachmentsLength = if Ptr AttachmentReference pResolveAttachments forall a. Eq a => a -> a -> Bool == forall a. Ptr a nullPtr then Int 0 else (forall a b. (Integral a, Num b) => a -> b fromIntegral Word32 colorAttachmentCount) Vector AttachmentReference pResolveAttachments' <- forall (m :: * -> *) a. Monad m => Int -> (Int -> m a) -> m (Vector a) generateM Int pResolveAttachmentsLength (\Int i -> forall a. FromCStruct a => Ptr a -> IO a peekCStruct @AttachmentReference ((Ptr AttachmentReference pResolveAttachments forall a. Ptr a -> Int -> Ptr a `advancePtrBytes` (Int 8 forall a. Num a => a -> a -> a * (Int i)) :: Ptr AttachmentReference))) Ptr AttachmentReference pDepthStencilAttachment <- forall a. Storable a => Ptr a -> IO a peek @(Ptr AttachmentReference) ((Ptr SubpassDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 48 :: Ptr (Ptr AttachmentReference))) Maybe AttachmentReference pDepthStencilAttachment' <- forall a b. (Ptr a -> IO b) -> Ptr a -> IO (Maybe b) maybePeek (\Ptr AttachmentReference j -> forall a. FromCStruct a => Ptr a -> IO a peekCStruct @AttachmentReference (Ptr AttachmentReference j)) Ptr AttachmentReference pDepthStencilAttachment Word32 preserveAttachmentCount <- forall a. Storable a => Ptr a -> IO a peek @Word32 ((Ptr SubpassDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 56 :: Ptr Word32)) Ptr Word32 pPreserveAttachments <- forall a. Storable a => Ptr a -> IO a peek @(Ptr Word32) ((Ptr SubpassDescription p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 64 :: Ptr (Ptr Word32))) Vector Word32 pPreserveAttachments' <- forall (m :: * -> *) a. Monad m => Int -> (Int -> m a) -> m (Vector a) generateM (forall a b. (Integral a, Num b) => a -> b fromIntegral Word32 preserveAttachmentCount) (\Int i -> forall a. Storable a => Ptr a -> IO a peek @Word32 ((Ptr Word32 pPreserveAttachments forall a. Ptr a -> Int -> Ptr a `advancePtrBytes` (Int 4 forall a. Num a => a -> a -> a * (Int i)) :: Ptr Word32))) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ SubpassDescriptionFlags -> PipelineBindPoint -> Vector AttachmentReference -> Vector AttachmentReference -> Vector AttachmentReference -> Maybe AttachmentReference -> Vector Word32 -> SubpassDescription SubpassDescription SubpassDescriptionFlags flags PipelineBindPoint pipelineBindPoint Vector AttachmentReference pInputAttachments' Vector AttachmentReference pColorAttachments' Vector AttachmentReference pResolveAttachments' Maybe AttachmentReference pDepthStencilAttachment' Vector Word32 pPreserveAttachments' instance Zero SubpassDescription where zero :: SubpassDescription zero = SubpassDescriptionFlags -> PipelineBindPoint -> Vector AttachmentReference -> Vector AttachmentReference -> Vector AttachmentReference -> Maybe AttachmentReference -> Vector Word32 -> SubpassDescription SubpassDescription forall a. Zero a => a zero forall a. Zero a => a zero forall a. Monoid a => a mempty forall a. Monoid a => a mempty forall a. Monoid a => a mempty forall a. Maybe a Nothing forall a. Monoid a => a mempty -- | VkSubpassDependency - Structure specifying a subpass dependency -- -- = Description -- -- If @srcSubpass@ is equal to @dstSubpass@ then the 'SubpassDependency' -- does not directly define a -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-dependencies dependency>. -- Instead, it enables pipeline barriers to be used in a render pass -- instance within the identified subpass, where the scopes of one pipeline -- barrier /must/ be a subset of those described by one subpass dependency. -- Subpass dependencies specified in this way that include -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-framebuffer-regions framebuffer-space stages> -- in the @srcStageMask@ /must/ only include -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-framebuffer-regions framebuffer-space stages> -- in @dstStageMask@, and /must/ include -- 'Vulkan.Core10.Enums.DependencyFlagBits.DEPENDENCY_BY_REGION_BIT'. When -- a subpass dependency is specified in this way for a subpass that has -- more than one view in its view mask, its @dependencyFlags@ /must/ -- include -- 'Vulkan.Core10.Enums.DependencyFlagBits.DEPENDENCY_VIEW_LOCAL_BIT'. -- -- If @srcSubpass@ and @dstSubpass@ are not equal, when a render pass -- instance which includes a subpass dependency is submitted to a queue, it -- defines a -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-dependencies dependency> -- between the subpasses identified by @srcSubpass@ and @dstSubpass@. -- -- If @srcSubpass@ is equal to -- 'Vulkan.Core10.APIConstants.SUBPASS_EXTERNAL', the first -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-dependencies-scopes synchronization scope> -- includes commands that occur earlier in -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-submission-order submission order> -- than the 'Vulkan.Core10.CommandBufferBuilding.cmdBeginRenderPass' used -- to begin the render pass instance. Otherwise, the first set of commands -- includes all commands submitted as part of the subpass instance -- identified by @srcSubpass@ and any -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#renderpass-load-operations load>, -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#renderpass-store-operations store>, -- or -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#renderpass-resolve-operations multisample resolve> -- operations on attachments used in @srcSubpass@. In either case, the -- first synchronization scope is limited to operations on the pipeline -- stages determined by the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-pipeline-stages-masks source stage mask> -- specified by @srcStageMask@. -- -- If @dstSubpass@ is equal to -- 'Vulkan.Core10.APIConstants.SUBPASS_EXTERNAL', the second -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-dependencies-scopes synchronization scope> -- includes commands that occur later in -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-submission-order submission order> -- than the 'Vulkan.Core10.CommandBufferBuilding.cmdEndRenderPass' used to -- end the render pass instance. Otherwise, the second set of commands -- includes all commands submitted as part of the subpass instance -- identified by @dstSubpass@ and any -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#renderpass-load-operations load>, -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#renderpass-store-operations store>, -- and -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#renderpass-resolve-operations multisample resolve> -- operations on attachments used in @dstSubpass@. In either case, the -- second synchronization scope is limited to operations on the pipeline -- stages determined by the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-pipeline-stages-masks destination stage mask> -- specified by @dstStageMask@. -- -- The first -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-dependencies-access-scopes access scope> -- is limited to accesses in the pipeline stages determined by the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-pipeline-stages-masks source stage mask> -- specified by @srcStageMask@. It is also limited to access types in the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-access-masks source access mask> -- specified by @srcAccessMask@. -- -- The second -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-dependencies-access-scopes access scope> -- is limited to accesses in the pipeline stages determined by the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-pipeline-stages-masks destination stage mask> -- specified by @dstStageMask@. It is also limited to access types in the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-access-masks destination access mask> -- specified by @dstAccessMask@. -- -- The -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-dependencies-available-and-visible availability and visibility operations> -- defined by a subpass dependency affect the execution of -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#renderpass-layout-transitions image layout transitions> -- within the render pass. -- -- Note -- -- For non-attachment resources, the memory dependency expressed by subpass -- dependency is nearly identical to that of a -- 'Vulkan.Core10.OtherTypes.MemoryBarrier' (with matching @srcAccessMask@ -- and @dstAccessMask@ parameters) submitted as a part of a -- 'Vulkan.Core10.CommandBufferBuilding.cmdPipelineBarrier' (with matching -- @srcStageMask@ and @dstStageMask@ parameters). The only difference being -- that its scopes are limited to the identified subpasses rather than -- potentially affecting everything before and after. -- -- For attachments however, subpass dependencies work more like a -- 'Vulkan.Core10.OtherTypes.ImageMemoryBarrier' defined similarly to the -- 'Vulkan.Core10.OtherTypes.MemoryBarrier' above, the queue family indices -- set to 'Vulkan.Core10.APIConstants.QUEUE_FAMILY_IGNORED', and layouts as -- follows: -- -- - The equivalent to @oldLayout@ is the attachment’s layout according -- to the subpass description for @srcSubpass@. -- -- - The equivalent to @newLayout@ is the attachment’s layout according -- to the subpass description for @dstSubpass@. -- -- == Valid Usage -- -- - #VUID-VkSubpassDependency-srcStageMask-04090# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-geometryShader geometryShader> -- feature is not enabled, @srcStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_GEOMETRY_SHADER_BIT' -- -- - #VUID-VkSubpassDependency-srcStageMask-04091# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-tessellationShader tessellationShader> -- feature is not enabled, @srcStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TESSELLATION_CONTROL_SHADER_BIT' -- or -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TESSELLATION_EVALUATION_SHADER_BIT' -- -- - #VUID-VkSubpassDependency-srcStageMask-04092# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-conditionalRendering conditionalRendering> -- feature is not enabled, @srcStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_CONDITIONAL_RENDERING_BIT_EXT' -- -- - #VUID-VkSubpassDependency-srcStageMask-04093# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-fragmentDensityMap fragmentDensityMap> -- feature is not enabled, @srcStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_FRAGMENT_DENSITY_PROCESS_BIT_EXT' -- -- - #VUID-VkSubpassDependency-srcStageMask-04094# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-transformFeedback transformFeedback> -- feature is not enabled, @srcStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TRANSFORM_FEEDBACK_BIT_EXT' -- -- - #VUID-VkSubpassDependency-srcStageMask-04095# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-meshShader meshShader> -- feature is not enabled, @srcStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_MESH_SHADER_BIT_EXT' -- -- - #VUID-VkSubpassDependency-srcStageMask-04096# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-taskShader taskShader> -- feature is not enabled, @srcStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TASK_SHADER_BIT_EXT' -- -- - #VUID-VkSubpassDependency-srcStageMask-07318# If neither the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shadingRateImage shadingRateImage> -- or -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-attachmentFragmentShadingRate attachmentFragmentShadingRate> -- are enabled, @srcStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_FRAGMENT_SHADING_RATE_ATTACHMENT_BIT_KHR' -- -- - #VUID-VkSubpassDependency-srcStageMask-03937# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-synchronization2 synchronization2> -- feature is not enabled, @srcStageMask@ /must/ not be @0@ -- -- - #VUID-VkSubpassDependency-srcStageMask-07949# If neither the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_NV_ray_tracing VK_NV_ray_tracing> -- extension or -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-rayTracingPipeline rayTracingPipeline feature> -- are enabled, @srcStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_RAY_TRACING_SHADER_BIT_KHR' -- -- - #VUID-VkSubpassDependency-dstStageMask-04090# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-geometryShader geometryShader> -- feature is not enabled, @dstStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_GEOMETRY_SHADER_BIT' -- -- - #VUID-VkSubpassDependency-dstStageMask-04091# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-tessellationShader tessellationShader> -- feature is not enabled, @dstStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TESSELLATION_CONTROL_SHADER_BIT' -- or -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TESSELLATION_EVALUATION_SHADER_BIT' -- -- - #VUID-VkSubpassDependency-dstStageMask-04092# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-conditionalRendering conditionalRendering> -- feature is not enabled, @dstStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_CONDITIONAL_RENDERING_BIT_EXT' -- -- - #VUID-VkSubpassDependency-dstStageMask-04093# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-fragmentDensityMap fragmentDensityMap> -- feature is not enabled, @dstStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_FRAGMENT_DENSITY_PROCESS_BIT_EXT' -- -- - #VUID-VkSubpassDependency-dstStageMask-04094# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-transformFeedback transformFeedback> -- feature is not enabled, @dstStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TRANSFORM_FEEDBACK_BIT_EXT' -- -- - #VUID-VkSubpassDependency-dstStageMask-04095# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-meshShader meshShader> -- feature is not enabled, @dstStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_MESH_SHADER_BIT_EXT' -- -- - #VUID-VkSubpassDependency-dstStageMask-04096# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-taskShader taskShader> -- feature is not enabled, @dstStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TASK_SHADER_BIT_EXT' -- -- - #VUID-VkSubpassDependency-dstStageMask-07318# If neither the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shadingRateImage shadingRateImage> -- or -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-attachmentFragmentShadingRate attachmentFragmentShadingRate> -- are enabled, @dstStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_FRAGMENT_SHADING_RATE_ATTACHMENT_BIT_KHR' -- -- - #VUID-VkSubpassDependency-dstStageMask-03937# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-synchronization2 synchronization2> -- feature is not enabled, @dstStageMask@ /must/ not be @0@ -- -- - #VUID-VkSubpassDependency-dstStageMask-07949# If neither the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_NV_ray_tracing VK_NV_ray_tracing> -- extension or -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-rayTracingPipeline rayTracingPipeline feature> -- are enabled, @dstStageMask@ /must/ not contain -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_RAY_TRACING_SHADER_BIT_KHR' -- -- - #VUID-VkSubpassDependency-srcSubpass-00864# @srcSubpass@ /must/ be -- less than or equal to @dstSubpass@, unless one of them is -- 'Vulkan.Core10.APIConstants.SUBPASS_EXTERNAL', to avoid cyclic -- dependencies and ensure a valid execution order -- -- - #VUID-VkSubpassDependency-srcSubpass-00865# @srcSubpass@ and -- @dstSubpass@ /must/ not both be equal to -- 'Vulkan.Core10.APIConstants.SUBPASS_EXTERNAL' -- -- - #VUID-VkSubpassDependency-srcSubpass-06809# If @srcSubpass@ is equal -- to @dstSubpass@ and @srcStageMask@ includes a -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-framebuffer-regions framebuffer-space stage>, -- @dstStageMask@ /must/ only contain -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-framebuffer-regions framebuffer-space stages> -- -- - #VUID-VkSubpassDependency-srcAccessMask-00868# Any access flag -- included in @srcAccessMask@ /must/ be supported by one of the -- pipeline stages in @srcStageMask@, as specified in the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-access-types-supported table of supported access types> -- -- - #VUID-VkSubpassDependency-dstAccessMask-00869# Any access flag -- included in @dstAccessMask@ /must/ be supported by one of the -- pipeline stages in @dstStageMask@, as specified in the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-access-types-supported table of supported access types> -- -- - #VUID-VkSubpassDependency-srcSubpass-02243# If @srcSubpass@ equals -- @dstSubpass@, and @srcStageMask@ and @dstStageMask@ both include a -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-framebuffer-regions framebuffer-space stage>, -- then @dependencyFlags@ /must/ include -- 'Vulkan.Core10.Enums.DependencyFlagBits.DEPENDENCY_BY_REGION_BIT' -- -- - #VUID-VkSubpassDependency-dependencyFlags-02520# If -- @dependencyFlags@ includes -- 'Vulkan.Core10.Enums.DependencyFlagBits.DEPENDENCY_VIEW_LOCAL_BIT', -- @srcSubpass@ /must/ not be equal to -- 'Vulkan.Core10.APIConstants.SUBPASS_EXTERNAL' -- -- - #VUID-VkSubpassDependency-dependencyFlags-02521# If -- @dependencyFlags@ includes -- 'Vulkan.Core10.Enums.DependencyFlagBits.DEPENDENCY_VIEW_LOCAL_BIT', -- @dstSubpass@ /must/ not be equal to -- 'Vulkan.Core10.APIConstants.SUBPASS_EXTERNAL' -- -- - #VUID-VkSubpassDependency-srcSubpass-00872# If @srcSubpass@ equals -- @dstSubpass@ and that subpass has more than one bit set in the view -- mask, then @dependencyFlags@ /must/ include -- 'Vulkan.Core10.Enums.DependencyFlagBits.DEPENDENCY_VIEW_LOCAL_BIT' -- -- == Valid Usage (Implicit) -- -- - #VUID-VkSubpassDependency-srcStageMask-parameter# @srcStageMask@ -- /must/ be a valid combination of -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PipelineStageFlagBits' -- values -- -- - #VUID-VkSubpassDependency-dstStageMask-parameter# @dstStageMask@ -- /must/ be a valid combination of -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PipelineStageFlagBits' -- values -- -- - #VUID-VkSubpassDependency-srcAccessMask-parameter# @srcAccessMask@ -- /must/ be a valid combination of -- 'Vulkan.Core10.Enums.AccessFlagBits.AccessFlagBits' values -- -- - #VUID-VkSubpassDependency-dstAccessMask-parameter# @dstAccessMask@ -- /must/ be a valid combination of -- 'Vulkan.Core10.Enums.AccessFlagBits.AccessFlagBits' values -- -- - #VUID-VkSubpassDependency-dependencyFlags-parameter# -- @dependencyFlags@ /must/ be a valid combination of -- 'Vulkan.Core10.Enums.DependencyFlagBits.DependencyFlagBits' values -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- 'Vulkan.Core10.Enums.AccessFlagBits.AccessFlags', -- 'Vulkan.Core10.Enums.DependencyFlagBits.DependencyFlags', -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PipelineStageFlags', -- 'RenderPassCreateInfo' data SubpassDependency = SubpassDependency { -- | @srcSubpass@ is the subpass index of the first subpass in the -- dependency, or 'Vulkan.Core10.APIConstants.SUBPASS_EXTERNAL'. SubpassDependency -> Word32 srcSubpass :: Word32 , -- | @dstSubpass@ is the subpass index of the second subpass in the -- dependency, or 'Vulkan.Core10.APIConstants.SUBPASS_EXTERNAL'. SubpassDependency -> Word32 dstSubpass :: Word32 , -- | @srcStageMask@ is a bitmask of -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PipelineStageFlagBits' -- specifying the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-pipeline-stages-masks source stage mask>. SubpassDependency -> PipelineStageFlags srcStageMask :: PipelineStageFlags , -- | @dstStageMask@ is a bitmask of -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PipelineStageFlagBits' -- specifying the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-pipeline-stages-masks destination stage mask> SubpassDependency -> PipelineStageFlags dstStageMask :: PipelineStageFlags , -- | @srcAccessMask@ is a bitmask of -- 'Vulkan.Core10.Enums.AccessFlagBits.AccessFlagBits' specifying a -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-access-masks source access mask>. SubpassDependency -> AccessFlags srcAccessMask :: AccessFlags , -- | @dstAccessMask@ is a bitmask of -- 'Vulkan.Core10.Enums.AccessFlagBits.AccessFlagBits' specifying a -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-access-masks destination access mask>. SubpassDependency -> AccessFlags dstAccessMask :: AccessFlags , -- | @dependencyFlags@ is a bitmask of -- 'Vulkan.Core10.Enums.DependencyFlagBits.DependencyFlagBits'. SubpassDependency -> DependencyFlags dependencyFlags :: DependencyFlags } deriving (Typeable, SubpassDependency -> SubpassDependency -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: SubpassDependency -> SubpassDependency -> Bool $c/= :: SubpassDependency -> SubpassDependency -> Bool == :: SubpassDependency -> SubpassDependency -> Bool $c== :: SubpassDependency -> SubpassDependency -> Bool Eq) #if defined(GENERIC_INSTANCES) deriving instance Generic (SubpassDependency) #endif deriving instance Show SubpassDependency instance ToCStruct SubpassDependency where withCStruct :: forall b. SubpassDependency -> (Ptr SubpassDependency -> IO b) -> IO b withCStruct SubpassDependency x Ptr SubpassDependency -> IO b f = forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes Int 28 forall a b. (a -> b) -> a -> b $ \Ptr SubpassDependency p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b pokeCStruct Ptr SubpassDependency p SubpassDependency x (Ptr SubpassDependency -> IO b f Ptr SubpassDependency p) pokeCStruct :: forall b. Ptr SubpassDependency -> SubpassDependency -> IO b -> IO b pokeCStruct Ptr SubpassDependency p SubpassDependency{Word32 DependencyFlags PipelineStageFlags AccessFlags dependencyFlags :: DependencyFlags dstAccessMask :: AccessFlags srcAccessMask :: AccessFlags dstStageMask :: PipelineStageFlags srcStageMask :: PipelineStageFlags dstSubpass :: Word32 srcSubpass :: Word32 $sel:dependencyFlags:SubpassDependency :: SubpassDependency -> DependencyFlags $sel:dstAccessMask:SubpassDependency :: SubpassDependency -> AccessFlags $sel:srcAccessMask:SubpassDependency :: SubpassDependency -> AccessFlags $sel:dstStageMask:SubpassDependency :: SubpassDependency -> PipelineStageFlags $sel:srcStageMask:SubpassDependency :: SubpassDependency -> PipelineStageFlags $sel:dstSubpass:SubpassDependency :: SubpassDependency -> Word32 $sel:srcSubpass:SubpassDependency :: SubpassDependency -> Word32 ..} IO b f = do forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr SubpassDependency p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr Word32)) (Word32 srcSubpass) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr SubpassDependency p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 4 :: Ptr Word32)) (Word32 dstSubpass) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr SubpassDependency p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr PipelineStageFlags)) (PipelineStageFlags srcStageMask) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr SubpassDependency p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 12 :: Ptr PipelineStageFlags)) (PipelineStageFlags dstStageMask) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr SubpassDependency p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr AccessFlags)) (AccessFlags srcAccessMask) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr SubpassDependency p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 20 :: Ptr AccessFlags)) (AccessFlags dstAccessMask) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr SubpassDependency p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 24 :: Ptr DependencyFlags)) (DependencyFlags dependencyFlags) IO b f cStructSize :: Int cStructSize = Int 28 cStructAlignment :: Int cStructAlignment = Int 4 pokeZeroCStruct :: forall b. Ptr SubpassDependency -> IO b -> IO b pokeZeroCStruct Ptr SubpassDependency p IO b f = do forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr SubpassDependency p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr Word32)) (forall a. Zero a => a zero) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr SubpassDependency p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 4 :: Ptr Word32)) (forall a. Zero a => a zero) IO b f instance FromCStruct SubpassDependency where peekCStruct :: Ptr SubpassDependency -> IO SubpassDependency peekCStruct Ptr SubpassDependency p = do Word32 srcSubpass <- forall a. Storable a => Ptr a -> IO a peek @Word32 ((Ptr SubpassDependency p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr Word32)) Word32 dstSubpass <- forall a. Storable a => Ptr a -> IO a peek @Word32 ((Ptr SubpassDependency p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 4 :: Ptr Word32)) PipelineStageFlags srcStageMask <- forall a. Storable a => Ptr a -> IO a peek @PipelineStageFlags ((Ptr SubpassDependency p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr PipelineStageFlags)) PipelineStageFlags dstStageMask <- forall a. Storable a => Ptr a -> IO a peek @PipelineStageFlags ((Ptr SubpassDependency p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 12 :: Ptr PipelineStageFlags)) AccessFlags srcAccessMask <- forall a. Storable a => Ptr a -> IO a peek @AccessFlags ((Ptr SubpassDependency p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr AccessFlags)) AccessFlags dstAccessMask <- forall a. Storable a => Ptr a -> IO a peek @AccessFlags ((Ptr SubpassDependency p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 20 :: Ptr AccessFlags)) DependencyFlags dependencyFlags <- forall a. Storable a => Ptr a -> IO a peek @DependencyFlags ((Ptr SubpassDependency p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 24 :: Ptr DependencyFlags)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ Word32 -> Word32 -> PipelineStageFlags -> PipelineStageFlags -> AccessFlags -> AccessFlags -> DependencyFlags -> SubpassDependency SubpassDependency Word32 srcSubpass Word32 dstSubpass PipelineStageFlags srcStageMask PipelineStageFlags dstStageMask AccessFlags srcAccessMask AccessFlags dstAccessMask DependencyFlags dependencyFlags instance Storable SubpassDependency where sizeOf :: SubpassDependency -> Int sizeOf ~SubpassDependency _ = Int 28 alignment :: SubpassDependency -> Int alignment ~SubpassDependency _ = Int 4 peek :: Ptr SubpassDependency -> IO SubpassDependency peek = forall a. FromCStruct a => Ptr a -> IO a peekCStruct poke :: Ptr SubpassDependency -> SubpassDependency -> IO () poke Ptr SubpassDependency ptr SubpassDependency poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b pokeCStruct Ptr SubpassDependency ptr SubpassDependency poked (forall (f :: * -> *) a. Applicative f => a -> f a pure ()) instance Zero SubpassDependency where zero :: SubpassDependency zero = Word32 -> Word32 -> PipelineStageFlags -> PipelineStageFlags -> AccessFlags -> AccessFlags -> DependencyFlags -> SubpassDependency SubpassDependency forall a. Zero a => a zero forall a. Zero a => a zero forall a. Zero a => a zero forall a. Zero a => a zero forall a. Zero a => a zero forall a. Zero a => a zero forall a. Zero a => a zero -- | VkRenderPassCreateInfo - Structure specifying parameters of a newly -- created render pass -- -- = Description -- -- Note -- -- Care should be taken to avoid a data race here; if any subpasses access -- attachments with overlapping memory locations, and one of those accesses -- is a write, a subpass dependency needs to be included between them. -- -- == Valid Usage -- -- - #VUID-VkRenderPassCreateInfo-attachment-00834# If the @attachment@ -- member of any element of @pInputAttachments@, @pColorAttachments@, -- @pResolveAttachments@ or @pDepthStencilAttachment@, or any element -- of @pPreserveAttachments@ in any element of @pSubpasses@ is not -- 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED', then it /must/ be -- less than @attachmentCount@ -- -- - #VUID-VkRenderPassCreateInfo-fragmentDensityMapAttachment-06471# If -- the pNext chain includes a -- 'Vulkan.Extensions.VK_EXT_fragment_density_map.RenderPassFragmentDensityMapCreateInfoEXT' -- structure and the @fragmentDensityMapAttachment@ member is not -- 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED', then @attachment@ -- /must/ be less than @attachmentCount@ -- -- - #VUID-VkRenderPassCreateInfo-pAttachments-00836# For any member of -- @pAttachments@ with a @loadOp@ equal to -- 'Vulkan.Core10.Enums.AttachmentLoadOp.ATTACHMENT_LOAD_OP_CLEAR', the -- first use of that attachment /must/ not specify a @layout@ equal to -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_SHADER_READ_ONLY_OPTIMAL' -- or -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL' -- -- - #VUID-VkRenderPassCreateInfo-pAttachments-02511# For any member of -- @pAttachments@ with a @stencilLoadOp@ equal to -- 'Vulkan.Core10.Enums.AttachmentLoadOp.ATTACHMENT_LOAD_OP_CLEAR', the -- first use of that attachment /must/ not specify a @layout@ equal to -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_SHADER_READ_ONLY_OPTIMAL' -- or -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL' -- -- - #VUID-VkRenderPassCreateInfo-pAttachments-01566# For any member of -- @pAttachments@ with a @loadOp@ equal to -- 'Vulkan.Core10.Enums.AttachmentLoadOp.ATTACHMENT_LOAD_OP_CLEAR', the -- first use of that attachment /must/ not specify a @layout@ equal to -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_STENCIL_ATTACHMENT_OPTIMAL' -- -- - #VUID-VkRenderPassCreateInfo-pAttachments-01567# For any member of -- @pAttachments@ with a @stencilLoadOp@ equal to -- 'Vulkan.Core10.Enums.AttachmentLoadOp.ATTACHMENT_LOAD_OP_CLEAR', the -- first use of that attachment /must/ not specify a @layout@ equal to -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_STENCIL_READ_ONLY_OPTIMAL' -- -- - #VUID-VkRenderPassCreateInfo-pNext-01926# If the @pNext@ chain -- includes a -- 'Vulkan.Core11.Promoted_From_VK_KHR_maintenance2.RenderPassInputAttachmentAspectCreateInfo' -- structure, the @subpass@ member of each element of its -- @pAspectReferences@ member /must/ be less than @subpassCount@ -- -- - #VUID-VkRenderPassCreateInfo-pNext-01927# If the @pNext@ chain -- includes a -- 'Vulkan.Core11.Promoted_From_VK_KHR_maintenance2.RenderPassInputAttachmentAspectCreateInfo' -- structure, the @inputAttachmentIndex@ member of each element of its -- @pAspectReferences@ member /must/ be less than the value of -- @inputAttachmentCount@ in the element of @pSubpasses@ identified by -- its @subpass@ member -- -- - #VUID-VkRenderPassCreateInfo-pNext-01963# If the @pNext@ chain -- includes a -- 'Vulkan.Core11.Promoted_From_VK_KHR_maintenance2.RenderPassInputAttachmentAspectCreateInfo' -- structure, for any element of the @pInputAttachments@ member of any -- element of @pSubpasses@ where the @attachment@ member is not -- 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED', the @aspectMask@ -- member of the corresponding element of -- 'Vulkan.Core11.Promoted_From_VK_KHR_maintenance2.RenderPassInputAttachmentAspectCreateInfo'::@pAspectReferences@ -- /must/ only include aspects that are present in images of the format -- specified by the element of @pAttachments@ at @attachment@ -- -- - #VUID-VkRenderPassCreateInfo-pNext-01928# If the @pNext@ chain -- includes a -- 'Vulkan.Core11.Promoted_From_VK_KHR_multiview.RenderPassMultiviewCreateInfo' -- structure, and its @subpassCount@ member is not zero, that member -- /must/ be equal to the value of @subpassCount@ -- -- - #VUID-VkRenderPassCreateInfo-pNext-01929# If the @pNext@ chain -- includes a -- 'Vulkan.Core11.Promoted_From_VK_KHR_multiview.RenderPassMultiviewCreateInfo' -- structure, if its @dependencyCount@ member is not zero, it /must/ be -- equal to @dependencyCount@ -- -- - #VUID-VkRenderPassCreateInfo-pNext-01930# If the @pNext@ chain -- includes a -- 'Vulkan.Core11.Promoted_From_VK_KHR_multiview.RenderPassMultiviewCreateInfo' -- structure, for each non-zero element of @pViewOffsets@, the -- @srcSubpass@ and @dstSubpass@ members of @pDependencies@ at the same -- index /must/ not be equal -- -- - #VUID-VkRenderPassCreateInfo-pNext-02512# If the @pNext@ chain -- includes a -- 'Vulkan.Core11.Promoted_From_VK_KHR_multiview.RenderPassMultiviewCreateInfo' -- structure, for any element of @pDependencies@ with a -- @dependencyFlags@ member that does not include -- 'Vulkan.Core10.Enums.DependencyFlagBits.DEPENDENCY_VIEW_LOCAL_BIT', -- the corresponding element of the @pViewOffsets@ member of that -- 'Vulkan.Core11.Promoted_From_VK_KHR_multiview.RenderPassMultiviewCreateInfo' -- instance /must/ be @0@ -- -- - #VUID-VkRenderPassCreateInfo-pNext-02513# If the @pNext@ chain -- includes a -- 'Vulkan.Core11.Promoted_From_VK_KHR_multiview.RenderPassMultiviewCreateInfo' -- structure, elements of its @pViewMasks@ member /must/ either all be -- @0@, or all not be @0@ -- -- - #VUID-VkRenderPassCreateInfo-pNext-02514# If the @pNext@ chain -- includes a -- 'Vulkan.Core11.Promoted_From_VK_KHR_multiview.RenderPassMultiviewCreateInfo' -- structure, and each element of its @pViewMasks@ member is @0@, the -- @dependencyFlags@ member of each element of @pDependencies@ /must/ -- not include -- 'Vulkan.Core10.Enums.DependencyFlagBits.DEPENDENCY_VIEW_LOCAL_BIT' -- -- - #VUID-VkRenderPassCreateInfo-pNext-02515# If the @pNext@ chain -- includes a -- 'Vulkan.Core11.Promoted_From_VK_KHR_multiview.RenderPassMultiviewCreateInfo' -- structure, and each element of its @pViewMasks@ member is @0@, its -- @correlationMaskCount@ member /must/ be @0@ -- -- - #VUID-VkRenderPassCreateInfo-pDependencies-00837# For any element of -- @pDependencies@, if the @srcSubpass@ is not -- 'Vulkan.Core10.APIConstants.SUBPASS_EXTERNAL', all stage flags -- included in the @srcStageMask@ member of that dependency /must/ be a -- pipeline stage supported by the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-pipeline-stages-types pipeline> -- identified by the @pipelineBindPoint@ member of the source subpass -- -- - #VUID-VkRenderPassCreateInfo-pDependencies-00838# For any element of -- @pDependencies@, if the @dstSubpass@ is not -- 'Vulkan.Core10.APIConstants.SUBPASS_EXTERNAL', all stage flags -- included in the @dstStageMask@ member of that dependency /must/ be a -- pipeline stage supported by the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-pipeline-stages-types pipeline> -- identified by the @pipelineBindPoint@ member of the destination -- subpass -- -- - #VUID-VkRenderPassCreateInfo-pDependencies-06866# For any element of -- @pDependencies@, if its @srcSubpass@ is not -- 'Vulkan.Core10.APIConstants.SUBPASS_EXTERNAL', it /must/ be less -- than @subpassCount@ -- -- - #VUID-VkRenderPassCreateInfo-pDependencies-06867# For any element of -- @pDependencies@, if its @dstSubpass@ is not -- 'Vulkan.Core10.APIConstants.SUBPASS_EXTERNAL', it /must/ be less -- than @subpassCount@ -- -- == Valid Usage (Implicit) -- -- - #VUID-VkRenderPassCreateInfo-sType-sType# @sType@ /must/ be -- 'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_RENDER_PASS_CREATE_INFO' -- -- - #VUID-VkRenderPassCreateInfo-pNext-pNext# Each @pNext@ member of any -- structure (including this one) in the @pNext@ chain /must/ be either -- @NULL@ or a pointer to a valid instance of -- 'Vulkan.Extensions.VK_EXT_fragment_density_map.RenderPassFragmentDensityMapCreateInfoEXT', -- 'Vulkan.Core11.Promoted_From_VK_KHR_maintenance2.RenderPassInputAttachmentAspectCreateInfo', -- or -- 'Vulkan.Core11.Promoted_From_VK_KHR_multiview.RenderPassMultiviewCreateInfo' -- -- - #VUID-VkRenderPassCreateInfo-sType-unique# The @sType@ value of each -- struct in the @pNext@ chain /must/ be unique -- -- - #VUID-VkRenderPassCreateInfo-flags-parameter# @flags@ /must/ be a -- valid combination of -- 'Vulkan.Core10.Enums.RenderPassCreateFlagBits.RenderPassCreateFlagBits' -- values -- -- - #VUID-VkRenderPassCreateInfo-pAttachments-parameter# If -- @attachmentCount@ is not @0@, @pAttachments@ /must/ be a valid -- pointer to an array of @attachmentCount@ valid -- 'AttachmentDescription' structures -- -- - #VUID-VkRenderPassCreateInfo-pSubpasses-parameter# @pSubpasses@ -- /must/ be a valid pointer to an array of @subpassCount@ valid -- 'SubpassDescription' structures -- -- - #VUID-VkRenderPassCreateInfo-pDependencies-parameter# If -- @dependencyCount@ is not @0@, @pDependencies@ /must/ be a valid -- pointer to an array of @dependencyCount@ valid 'SubpassDependency' -- structures -- -- - #VUID-VkRenderPassCreateInfo-subpassCount-arraylength# -- @subpassCount@ /must/ be greater than @0@ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- 'AttachmentDescription', -- 'Vulkan.Core10.Enums.RenderPassCreateFlagBits.RenderPassCreateFlags', -- 'Vulkan.Core10.Enums.StructureType.StructureType', 'SubpassDependency', -- 'SubpassDescription', 'createRenderPass' data RenderPassCreateInfo (es :: [Type]) = RenderPassCreateInfo { -- | @pNext@ is @NULL@ or a pointer to a structure extending this structure. forall (es :: [*]). RenderPassCreateInfo es -> Chain es next :: Chain es , -- | @flags@ is a bitmask of -- 'Vulkan.Core10.Enums.RenderPassCreateFlagBits.RenderPassCreateFlagBits' forall (es :: [*]). RenderPassCreateInfo es -> RenderPassCreateFlags flags :: RenderPassCreateFlags , -- | @pAttachments@ is a pointer to an array of @attachmentCount@ -- 'AttachmentDescription' structures describing the attachments used by -- the render pass. forall (es :: [*]). RenderPassCreateInfo es -> Vector AttachmentDescription attachments :: Vector AttachmentDescription , -- | @pSubpasses@ is a pointer to an array of @subpassCount@ -- 'SubpassDescription' structures describing each subpass. forall (es :: [*]). RenderPassCreateInfo es -> Vector SubpassDescription subpasses :: Vector SubpassDescription , -- | @pDependencies@ is a pointer to an array of @dependencyCount@ -- 'SubpassDependency' structures describing dependencies between pairs of -- subpasses. forall (es :: [*]). RenderPassCreateInfo es -> Vector SubpassDependency dependencies :: Vector SubpassDependency } deriving (Typeable) #if defined(GENERIC_INSTANCES) deriving instance Generic (RenderPassCreateInfo (es :: [Type])) #endif deriving instance Show (Chain es) => Show (RenderPassCreateInfo es) instance Extensible RenderPassCreateInfo where extensibleTypeName :: String extensibleTypeName = String "RenderPassCreateInfo" setNext :: forall (ds :: [*]) (es :: [*]). RenderPassCreateInfo ds -> Chain es -> RenderPassCreateInfo es setNext RenderPassCreateInfo{Vector SubpassDescription Vector SubpassDependency Vector AttachmentDescription Chain ds RenderPassCreateFlags dependencies :: Vector SubpassDependency subpasses :: Vector SubpassDescription attachments :: Vector AttachmentDescription flags :: RenderPassCreateFlags next :: Chain ds $sel:dependencies:RenderPassCreateInfo :: forall (es :: [*]). RenderPassCreateInfo es -> Vector SubpassDependency $sel:subpasses:RenderPassCreateInfo :: forall (es :: [*]). RenderPassCreateInfo es -> Vector SubpassDescription $sel:attachments:RenderPassCreateInfo :: forall (es :: [*]). RenderPassCreateInfo es -> Vector AttachmentDescription $sel:flags:RenderPassCreateInfo :: forall (es :: [*]). RenderPassCreateInfo es -> RenderPassCreateFlags $sel:next:RenderPassCreateInfo :: forall (es :: [*]). RenderPassCreateInfo es -> Chain es ..} Chain es next' = RenderPassCreateInfo{$sel:next:RenderPassCreateInfo :: Chain es next = Chain es next', Vector SubpassDescription Vector SubpassDependency Vector AttachmentDescription RenderPassCreateFlags dependencies :: Vector SubpassDependency subpasses :: Vector SubpassDescription attachments :: Vector AttachmentDescription flags :: RenderPassCreateFlags $sel:dependencies:RenderPassCreateInfo :: Vector SubpassDependency $sel:subpasses:RenderPassCreateInfo :: Vector SubpassDescription $sel:attachments:RenderPassCreateInfo :: Vector AttachmentDescription $sel:flags:RenderPassCreateInfo :: RenderPassCreateFlags ..} getNext :: forall (es :: [*]). RenderPassCreateInfo es -> Chain es getNext RenderPassCreateInfo{Vector SubpassDescription Vector SubpassDependency Vector AttachmentDescription Chain es RenderPassCreateFlags dependencies :: Vector SubpassDependency subpasses :: Vector SubpassDescription attachments :: Vector AttachmentDescription flags :: RenderPassCreateFlags next :: Chain es $sel:dependencies:RenderPassCreateInfo :: forall (es :: [*]). RenderPassCreateInfo es -> Vector SubpassDependency $sel:subpasses:RenderPassCreateInfo :: forall (es :: [*]). RenderPassCreateInfo es -> Vector SubpassDescription $sel:attachments:RenderPassCreateInfo :: forall (es :: [*]). RenderPassCreateInfo es -> Vector AttachmentDescription $sel:flags:RenderPassCreateInfo :: forall (es :: [*]). RenderPassCreateInfo es -> RenderPassCreateFlags $sel:next:RenderPassCreateInfo :: forall (es :: [*]). RenderPassCreateInfo es -> Chain es ..} = Chain es next extends :: forall e b proxy. Typeable e => proxy e -> (Extends RenderPassCreateInfo e => b) -> Maybe b extends :: forall e b (proxy :: * -> *). Typeable e => proxy e -> (Extends RenderPassCreateInfo e => b) -> Maybe b extends proxy e _ Extends RenderPassCreateInfo e => b f | Just e :~: RenderPassFragmentDensityMapCreateInfoEXT Refl <- forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => Maybe (a :~: b) eqT @e @RenderPassFragmentDensityMapCreateInfoEXT = forall a. a -> Maybe a Just Extends RenderPassCreateInfo e => b f | Just e :~: RenderPassInputAttachmentAspectCreateInfo Refl <- forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => Maybe (a :~: b) eqT @e @RenderPassInputAttachmentAspectCreateInfo = forall a. a -> Maybe a Just Extends RenderPassCreateInfo e => b f | Just e :~: RenderPassMultiviewCreateInfo Refl <- forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => Maybe (a :~: b) eqT @e @RenderPassMultiviewCreateInfo = forall a. a -> Maybe a Just Extends RenderPassCreateInfo e => b f | Bool otherwise = forall a. Maybe a Nothing instance ( Extendss RenderPassCreateInfo es , PokeChain es ) => ToCStruct (RenderPassCreateInfo es) where withCStruct :: forall b. RenderPassCreateInfo es -> (Ptr (RenderPassCreateInfo es) -> IO b) -> IO b withCStruct RenderPassCreateInfo es x Ptr (RenderPassCreateInfo es) -> IO b f = forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes Int 64 forall a b. (a -> b) -> a -> b $ \Ptr (RenderPassCreateInfo es) p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b pokeCStruct Ptr (RenderPassCreateInfo es) p RenderPassCreateInfo es x (Ptr (RenderPassCreateInfo es) -> IO b f Ptr (RenderPassCreateInfo es) p) pokeCStruct :: forall b. Ptr (RenderPassCreateInfo es) -> RenderPassCreateInfo es -> IO b -> IO b pokeCStruct Ptr (RenderPassCreateInfo es) p RenderPassCreateInfo{Vector SubpassDescription Vector SubpassDependency Vector AttachmentDescription Chain es RenderPassCreateFlags dependencies :: Vector SubpassDependency subpasses :: Vector SubpassDescription attachments :: Vector AttachmentDescription flags :: RenderPassCreateFlags next :: Chain es $sel:dependencies:RenderPassCreateInfo :: forall (es :: [*]). RenderPassCreateInfo es -> Vector SubpassDependency $sel:subpasses:RenderPassCreateInfo :: forall (es :: [*]). RenderPassCreateInfo es -> Vector SubpassDescription $sel:attachments:RenderPassCreateInfo :: forall (es :: [*]). RenderPassCreateInfo es -> Vector AttachmentDescription $sel:flags:RenderPassCreateInfo :: forall (es :: [*]). RenderPassCreateInfo es -> RenderPassCreateFlags $sel:next:RenderPassCreateInfo :: forall (es :: [*]). RenderPassCreateInfo es -> Chain es ..} IO b f = forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT forall a b. (a -> b) -> a -> b $ do forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (RenderPassCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr StructureType)) (StructureType STRUCTURE_TYPE_RENDER_PASS_CREATE_INFO) Ptr () pNext'' <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap forall a b. Ptr a -> Ptr b castPtr forall b c a. (b -> c) -> (a -> b) -> a -> c . forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall (es :: [*]) a. PokeChain es => Chain es -> (Ptr (Chain es) -> IO a) -> IO a withChain (Chain es next) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (RenderPassCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr (Ptr ()))) Ptr () pNext'' forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (RenderPassCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr RenderPassCreateFlags)) (RenderPassCreateFlags flags) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (RenderPassCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 20 :: Ptr Word32)) ((forall a b. (Integral a, Num b) => a -> b fromIntegral (forall a. Vector a -> Int Data.Vector.length forall a b. (a -> b) -> a -> b $ (Vector AttachmentDescription attachments)) :: Word32)) Ptr AttachmentDescription pPAttachments' <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes @AttachmentDescription ((forall a. Vector a -> Int Data.Vector.length (Vector AttachmentDescription attachments)) forall a. Num a => a -> a -> a * Int 36) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\Int i AttachmentDescription e -> forall a. Storable a => Ptr a -> a -> IO () poke (Ptr AttachmentDescription pPAttachments' forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 36 forall a. Num a => a -> a -> a * (Int i)) :: Ptr AttachmentDescription) (AttachmentDescription e)) (Vector AttachmentDescription attachments) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (RenderPassCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 24 :: Ptr (Ptr AttachmentDescription))) (Ptr AttachmentDescription pPAttachments') forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (RenderPassCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 32 :: Ptr Word32)) ((forall a b. (Integral a, Num b) => a -> b fromIntegral (forall a. Vector a -> Int Data.Vector.length forall a b. (a -> b) -> a -> b $ (Vector SubpassDescription subpasses)) :: Word32)) Ptr SubpassDescription pPSubpasses' <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes @SubpassDescription ((forall a. Vector a -> Int Data.Vector.length (Vector SubpassDescription subpasses)) forall a. Num a => a -> a -> a * Int 72) forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\Int i SubpassDescription e -> forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b pokeCStruct (Ptr SubpassDescription pPSubpasses' forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 72 forall a. Num a => a -> a -> a * (Int i)) :: Ptr SubpassDescription) (SubpassDescription e) forall b c a. (b -> c) -> (a -> b) -> a -> c . (forall a b. (a -> b) -> a -> b $ ())) (Vector SubpassDescription subpasses) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (RenderPassCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 40 :: Ptr (Ptr SubpassDescription))) (Ptr SubpassDescription pPSubpasses') forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (RenderPassCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 48 :: Ptr Word32)) ((forall a b. (Integral a, Num b) => a -> b fromIntegral (forall a. Vector a -> Int Data.Vector.length forall a b. (a -> b) -> a -> b $ (Vector SubpassDependency dependencies)) :: Word32)) Ptr SubpassDependency pPDependencies' <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes @SubpassDependency ((forall a. Vector a -> Int Data.Vector.length (Vector SubpassDependency dependencies)) forall a. Num a => a -> a -> a * Int 28) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\Int i SubpassDependency e -> forall a. Storable a => Ptr a -> a -> IO () poke (Ptr SubpassDependency pPDependencies' forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 28 forall a. Num a => a -> a -> a * (Int i)) :: Ptr SubpassDependency) (SubpassDependency e)) (Vector SubpassDependency dependencies) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (RenderPassCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 56 :: Ptr (Ptr SubpassDependency))) (Ptr SubpassDependency pPDependencies') forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ IO b f cStructSize :: Int cStructSize = Int 64 cStructAlignment :: Int cStructAlignment = Int 8 pokeZeroCStruct :: forall b. Ptr (RenderPassCreateInfo es) -> IO b -> IO b pokeZeroCStruct Ptr (RenderPassCreateInfo es) p IO b f = forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT forall a b. (a -> b) -> a -> b $ do forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (RenderPassCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr StructureType)) (StructureType STRUCTURE_TYPE_RENDER_PASS_CREATE_INFO) Ptr () pNext' <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap forall a b. Ptr a -> Ptr b castPtr forall b c a. (b -> c) -> (a -> b) -> a -> c . forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall (es :: [*]) a. PokeChain es => (Ptr (Chain es) -> IO a) -> IO a withZeroChain @es forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (RenderPassCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr (Ptr ()))) Ptr () pNext' forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ IO b f instance ( Extendss RenderPassCreateInfo es , PeekChain es ) => FromCStruct (RenderPassCreateInfo es) where peekCStruct :: Ptr (RenderPassCreateInfo es) -> IO (RenderPassCreateInfo es) peekCStruct Ptr (RenderPassCreateInfo es) p = do Ptr () pNext <- forall a. Storable a => Ptr a -> IO a peek @(Ptr ()) ((Ptr (RenderPassCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr (Ptr ()))) Chain es next <- forall (es :: [*]). PeekChain es => Ptr (Chain es) -> IO (Chain es) peekChain (forall a b. Ptr a -> Ptr b castPtr Ptr () pNext) RenderPassCreateFlags flags <- forall a. Storable a => Ptr a -> IO a peek @RenderPassCreateFlags ((Ptr (RenderPassCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr RenderPassCreateFlags)) Word32 attachmentCount <- forall a. Storable a => Ptr a -> IO a peek @Word32 ((Ptr (RenderPassCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 20 :: Ptr Word32)) Ptr AttachmentDescription pAttachments <- forall a. Storable a => Ptr a -> IO a peek @(Ptr AttachmentDescription) ((Ptr (RenderPassCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 24 :: Ptr (Ptr AttachmentDescription))) Vector AttachmentDescription pAttachments' <- forall (m :: * -> *) a. Monad m => Int -> (Int -> m a) -> m (Vector a) generateM (forall a b. (Integral a, Num b) => a -> b fromIntegral Word32 attachmentCount) (\Int i -> forall a. FromCStruct a => Ptr a -> IO a peekCStruct @AttachmentDescription ((Ptr AttachmentDescription pAttachments forall a. Ptr a -> Int -> Ptr a `advancePtrBytes` (Int 36 forall a. Num a => a -> a -> a * (Int i)) :: Ptr AttachmentDescription))) Word32 subpassCount <- forall a. Storable a => Ptr a -> IO a peek @Word32 ((Ptr (RenderPassCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 32 :: Ptr Word32)) Ptr SubpassDescription pSubpasses <- forall a. Storable a => Ptr a -> IO a peek @(Ptr SubpassDescription) ((Ptr (RenderPassCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 40 :: Ptr (Ptr SubpassDescription))) Vector SubpassDescription pSubpasses' <- forall (m :: * -> *) a. Monad m => Int -> (Int -> m a) -> m (Vector a) generateM (forall a b. (Integral a, Num b) => a -> b fromIntegral Word32 subpassCount) (\Int i -> forall a. FromCStruct a => Ptr a -> IO a peekCStruct @SubpassDescription ((Ptr SubpassDescription pSubpasses forall a. Ptr a -> Int -> Ptr a `advancePtrBytes` (Int 72 forall a. Num a => a -> a -> a * (Int i)) :: Ptr SubpassDescription))) Word32 dependencyCount <- forall a. Storable a => Ptr a -> IO a peek @Word32 ((Ptr (RenderPassCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 48 :: Ptr Word32)) Ptr SubpassDependency pDependencies <- forall a. Storable a => Ptr a -> IO a peek @(Ptr SubpassDependency) ((Ptr (RenderPassCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 56 :: Ptr (Ptr SubpassDependency))) Vector SubpassDependency pDependencies' <- forall (m :: * -> *) a. Monad m => Int -> (Int -> m a) -> m (Vector a) generateM (forall a b. (Integral a, Num b) => a -> b fromIntegral Word32 dependencyCount) (\Int i -> forall a. FromCStruct a => Ptr a -> IO a peekCStruct @SubpassDependency ((Ptr SubpassDependency pDependencies forall a. Ptr a -> Int -> Ptr a `advancePtrBytes` (Int 28 forall a. Num a => a -> a -> a * (Int i)) :: Ptr SubpassDependency))) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ forall (es :: [*]). Chain es -> RenderPassCreateFlags -> Vector AttachmentDescription -> Vector SubpassDescription -> Vector SubpassDependency -> RenderPassCreateInfo es RenderPassCreateInfo Chain es next RenderPassCreateFlags flags Vector AttachmentDescription pAttachments' Vector SubpassDescription pSubpasses' Vector SubpassDependency pDependencies' instance es ~ '[] => Zero (RenderPassCreateInfo es) where zero :: RenderPassCreateInfo es zero = forall (es :: [*]). Chain es -> RenderPassCreateFlags -> Vector AttachmentDescription -> Vector SubpassDescription -> Vector SubpassDependency -> RenderPassCreateInfo es RenderPassCreateInfo () forall a. Zero a => a zero forall a. Monoid a => a mempty forall a. Monoid a => a mempty forall a. Monoid a => a mempty -- | VkFramebufferCreateInfo - Structure specifying parameters of a newly -- created framebuffer -- -- = Description -- -- It is legal for a subpass to use no color or depth\/stencil attachments, -- either because it has no attachment references or because all of them -- are 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED'. This kind of subpass -- /can/ use shader side effects such as image stores and atomics to -- produce an output. In this case, the subpass continues to use the -- @width@, @height@, and @layers@ of the framebuffer to define the -- dimensions of the rendering area, and the @rasterizationSamples@ from -- each pipeline’s -- 'Vulkan.Core10.Pipeline.PipelineMultisampleStateCreateInfo' to define -- the number of samples used in rasterization; however, if -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceFeatures'::@variableMultisampleRate@ -- is 'Vulkan.Core10.FundamentalTypes.FALSE', then all pipelines to be -- bound with the subpass /must/ have the same value for -- 'Vulkan.Core10.Pipeline.PipelineMultisampleStateCreateInfo'::@rasterizationSamples@. -- In all such cases, @rasterizationSamples@ /must/ be a bit value that is -- set in -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@framebufferNoAttachmentsSampleCounts@. -- -- == Valid Usage -- -- - #VUID-VkFramebufferCreateInfo-attachmentCount-00876# -- @attachmentCount@ /must/ be equal to the attachment count specified -- in @renderPass@ -- -- - #VUID-VkFramebufferCreateInfo-flags-02778# If @flags@ does not -- include -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT' -- and @attachmentCount@ is not @0@, @pAttachments@ /must/ be a valid -- pointer to an array of @attachmentCount@ valid -- 'Vulkan.Core10.Handles.ImageView' handles -- -- - #VUID-VkFramebufferCreateInfo-pAttachments-00877# If @flags@ does -- not include -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT', -- each element of @pAttachments@ that is used as a color attachment or -- resolve attachment by @renderPass@ /must/ have been created with a -- @usage@ value including -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_COLOR_ATTACHMENT_BIT' -- -- - #VUID-VkFramebufferCreateInfo-pAttachments-02633# If @flags@ does -- not include -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT', -- each element of @pAttachments@ that is used as a depth\/stencil -- attachment by @renderPass@ /must/ have been created with a @usage@ -- value including -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_DEPTH_STENCIL_ATTACHMENT_BIT' -- -- - #VUID-VkFramebufferCreateInfo-pAttachments-02634# If @flags@ does -- not include -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT', -- each element of @pAttachments@ that is used as a depth\/stencil -- resolve attachment by @renderPass@ /must/ have been created with a -- @usage@ value including -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_DEPTH_STENCIL_ATTACHMENT_BIT' -- -- - #VUID-VkFramebufferCreateInfo-pAttachments-00879# If @renderpass@ is -- not 'Vulkan.Core10.APIConstants.NULL_HANDLE', @flags@ does not -- include -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT', -- each element of @pAttachments@ that is used as an input attachment -- by @renderPass@ /must/ have been created with a @usage@ value -- including -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_INPUT_ATTACHMENT_BIT' -- -- - #VUID-VkFramebufferCreateInfo-pAttachments-02552# Each element of -- @pAttachments@ that is used as a fragment density map attachment by -- @renderPass@ /must/ not have been created with a @flags@ value -- including -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SUBSAMPLED_BIT_EXT' -- -- - #VUID-VkFramebufferCreateInfo-renderPass-02553# If @renderPass@ has -- a fragment density map attachment and the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-fragmentDensityMapNonSubsampledImages fragmentDensityMapNonSubsampledImages> -- feature is not enabled, each element of @pAttachments@ /must/ have -- been created with a @flags@ value including -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SUBSAMPLED_BIT_EXT' -- unless that element is the fragment density map attachment -- -- - #VUID-VkFramebufferCreateInfo-renderPass-06502# If @renderPass@ was -- created with -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#renderpass-fragmentdensitymapoffsets fragment density map offsets> -- other than (0,0), each element of @pAttachments@ /must/ have been -- created with a @flags@ value including -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_FRAGMENT_DENSITY_MAP_OFFSET_BIT_QCOM' -- -- - #VUID-VkFramebufferCreateInfo-pAttachments-00880# If @flags@ does -- not include -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT', -- each element of @pAttachments@ /must/ have been created with a -- 'Vulkan.Core10.Enums.Format.Format' value that matches the -- 'Vulkan.Core10.Enums.Format.Format' specified by the corresponding -- 'AttachmentDescription' in @renderPass@ -- -- - #VUID-VkFramebufferCreateInfo-pAttachments-00881# If @flags@ does -- not include -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT', -- each element of @pAttachments@ /must/ have been created with a -- @samples@ value that matches the @samples@ value specified by the -- corresponding 'AttachmentDescription' in @renderPass@ -- -- - #VUID-VkFramebufferCreateInfo-flags-04533# If @flags@ does not -- include -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT', -- each element of @pAttachments@ that is used as an input, color, -- resolve, or depth\/stencil attachment by @renderPass@ /must/ have -- been created with a -- 'Vulkan.Core10.Image.ImageCreateInfo'::@extent.width@ greater than -- or equal to @width@ -- -- - #VUID-VkFramebufferCreateInfo-flags-04534# If @flags@ does not -- include -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT', -- each element of @pAttachments@ that is used as an input, color, -- resolve, or depth\/stencil attachment by @renderPass@ /must/ have -- been created with a -- 'Vulkan.Core10.Image.ImageCreateInfo'::@extent.height@ greater than -- or equal to @height@ -- -- - #VUID-VkFramebufferCreateInfo-flags-04535# If @flags@ does not -- include -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT', -- each element of @pAttachments@ that is used as an input, color, -- resolve, or depth\/stencil attachment by @renderPass@ /must/ have -- been created with a -- 'Vulkan.Core10.ImageView.ImageViewCreateInfo'::@subresourceRange.layerCount@ -- greater than or equal to @layers@ -- -- - #VUID-VkFramebufferCreateInfo-renderPass-04536# If @renderPass@ was -- specified with non-zero view masks, each element of @pAttachments@ -- that is used as an input, color, resolve, or depth\/stencil -- attachment by @renderPass@ /must/ have a @layerCount@ greater than -- the index of the most significant bit set in any of those view masks -- -- - #VUID-VkFramebufferCreateInfo-renderPass-02746# Each element of -- @pAttachments@ that is referenced by @fragmentDensityMapAttachment@ -- /must/ have a @layerCount@ equal to @1@ or if @renderPass@ was -- specified with non-zero view masks, greater than the index of the -- most significant bit set in any of those view masks -- -- - #VUID-VkFramebufferCreateInfo-pAttachments-02555# If @flags@ does -- not include -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT', -- an element of @pAttachments@ that is referenced by -- @fragmentDensityMapAttachment@ /must/ have a width at least as large -- as -- \(\left\lceil{\frac{width}{maxFragmentDensityTexelSize_{width}}}\right\rceil\) -- -- - #VUID-VkFramebufferCreateInfo-pAttachments-02556# If @flags@ does -- not include -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT', -- an element of @pAttachments@ that is referenced by -- @fragmentDensityMapAttachment@ /must/ have a height at least as -- large as -- \(\left\lceil{\frac{height}{maxFragmentDensityTexelSize_{height}}}\right\rceil\) -- -- - #VUID-VkFramebufferCreateInfo-flags-04537# If @flags@ does not -- include -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT', -- and @renderPass@ was specified with non-zero view masks, each -- element of @pAttachments@ that is used as a -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#primsrast-fragment-shading-rate-attachment fragment shading rate attachment> -- by @renderPass@ /must/ have a @layerCount@ that is either @1@, or -- greater than the index of the most significant bit set in any of -- those view masks -- -- - #VUID-VkFramebufferCreateInfo-flags-04538# If @flags@ does not -- include -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT', -- and @renderPass@ was not specified with non-zero view masks, each -- element of @pAttachments@ that is used as a -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#primsrast-fragment-shading-rate-attachment fragment shading rate attachment> -- by @renderPass@ /must/ have a @layerCount@ that is either @1@, or -- greater than @layers@ -- -- - #VUID-VkFramebufferCreateInfo-renderPass-08921# If @renderPass@ was -- specified with non-zero view masks, each element of @pAttachments@ -- that is used as a -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#primsrast-fragment-shading-rate-attachment fragment shading rate attachment> -- /must/ have a @layerCount@ equal to @1@ or greater than the index of -- the most significant bit set in any of those view masks -- -- - #VUID-VkFramebufferCreateInfo-flags-04539# If @flags@ does not -- include -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT', -- an element of @pAttachments@ that is used as a -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#primsrast-fragment-shading-rate-attachment fragment shading rate attachment> -- /must/ have a width at least as large as ⌈@width@ \/ @texelWidth@⌉, -- where @texelWidth@ is the largest value of -- @shadingRateAttachmentTexelSize.width@ in a -- 'Vulkan.Extensions.VK_KHR_fragment_shading_rate.FragmentShadingRateAttachmentInfoKHR' -- which references that attachment -- -- - #VUID-VkFramebufferCreateInfo-flags-04540# If @flags@ does not -- include -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT', -- an element of @pAttachments@ that is used as a -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#primsrast-fragment-shading-rate-attachment fragment shading rate attachment> -- /must/ have a height at least as large as ⌈@height@ \/ -- @texelHeight@⌉, where @texelHeight@ is the largest value of -- @shadingRateAttachmentTexelSize.height@ in a -- 'Vulkan.Extensions.VK_KHR_fragment_shading_rate.FragmentShadingRateAttachmentInfoKHR' -- which references that attachment -- -- - #VUID-VkFramebufferCreateInfo-pAttachments-00883# If @flags@ does -- not include -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT', -- each element of @pAttachments@ /must/ only specify a single mip -- level -- -- - #VUID-VkFramebufferCreateInfo-pAttachments-00884# If @flags@ does -- not include -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT', -- each element of @pAttachments@ /must/ have been created with the -- identity swizzle -- -- - #VUID-VkFramebufferCreateInfo-width-00885# @width@ /must/ be greater -- than @0@ -- -- - #VUID-VkFramebufferCreateInfo-width-00886# @width@ /must/ be less -- than or equal to -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#limits-maxFramebufferWidth maxFramebufferWidth> -- -- - #VUID-VkFramebufferCreateInfo-height-00887# @height@ /must/ be -- greater than @0@ -- -- - #VUID-VkFramebufferCreateInfo-height-00888# @height@ /must/ be less -- than or equal to -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#limits-maxFramebufferHeight maxFramebufferHeight> -- -- - #VUID-VkFramebufferCreateInfo-layers-00889# @layers@ /must/ be -- greater than @0@ -- -- - #VUID-VkFramebufferCreateInfo-layers-00890# @layers@ /must/ be less -- than or equal to -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#limits-maxFramebufferLayers maxFramebufferLayers> -- -- - #VUID-VkFramebufferCreateInfo-renderPass-02531# If @renderPass@ was -- specified with non-zero view masks, @layers@ /must/ be @1@ -- -- - #VUID-VkFramebufferCreateInfo-pAttachments-00891# If @flags@ does -- not include -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT', -- each element of @pAttachments@ that is a 2D or 2D array image view -- taken from a 3D image /must/ not be a depth\/stencil format -- -- - #VUID-VkFramebufferCreateInfo-flags-03189# If the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-imagelessFramebuffer imagelessFramebuffer> -- feature is not enabled, @flags@ /must/ not include -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT' -- -- - #VUID-VkFramebufferCreateInfo-flags-03190# If @flags@ includes -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT', -- the @pNext@ chain /must/ include a -- 'Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer.FramebufferAttachmentsCreateInfo' -- structure -- -- - #VUID-VkFramebufferCreateInfo-flags-03191# If @flags@ includes -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT', -- the @attachmentImageInfoCount@ member of a -- 'Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer.FramebufferAttachmentsCreateInfo' -- structure in the @pNext@ chain /must/ be equal to either zero or -- @attachmentCount@ -- -- - #VUID-VkFramebufferCreateInfo-flags-04541# If @flags@ includes -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT', -- the @width@ member of any element of the @pAttachmentImageInfos@ -- member of a -- 'Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer.FramebufferAttachmentsCreateInfo' -- structure in the @pNext@ chain that is used as an input, color, -- resolve or depth\/stencil attachment in @renderPass@ /must/ be -- greater than or equal to @width@ -- -- - #VUID-VkFramebufferCreateInfo-flags-04542# If @flags@ includes -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT', -- the @height@ member of any element of the @pAttachmentImageInfos@ -- member of a -- 'Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer.FramebufferAttachmentsCreateInfo' -- structure in the @pNext@ chain that is used as an input, color, -- resolve or depth\/stencil attachment in @renderPass@ /must/ be -- greater than or equal to @height@ -- -- - #VUID-VkFramebufferCreateInfo-flags-03196# If @flags@ includes -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT', -- the @width@ member of any element of the @pAttachmentImageInfos@ -- member of a -- 'Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer.FramebufferAttachmentsCreateInfo' -- structure in the @pNext@ chain that is referenced by -- 'Vulkan.Extensions.VK_EXT_fragment_density_map.RenderPassFragmentDensityMapCreateInfoEXT'::@fragmentDensityMapAttachment@ -- in @renderPass@ /must/ be greater than or equal to -- \(\left\lceil{\frac{width}{maxFragmentDensityTexelSize_{width}}}\right\rceil\) -- -- - #VUID-VkFramebufferCreateInfo-flags-03197# If @flags@ includes -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT', -- the @height@ member of any element of the @pAttachmentImageInfos@ -- member of a -- 'Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer.FramebufferAttachmentsCreateInfo' -- structure included in the @pNext@ chain that is referenced by -- 'Vulkan.Extensions.VK_EXT_fragment_density_map.RenderPassFragmentDensityMapCreateInfoEXT'::@fragmentDensityMapAttachment@ -- in @renderPass@ /must/ be greater than or equal to -- \(\left\lceil{\frac{height}{maxFragmentDensityTexelSize_{height}}}\right\rceil\) -- -- - #VUID-VkFramebufferCreateInfo-flags-04543# If @flags@ includes -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT', -- the @width@ member of any element of the @pAttachmentImageInfos@ -- member of a -- 'Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer.FramebufferAttachmentsCreateInfo' -- structure in the @pNext@ chain that is used as a -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#primsrast-fragment-shading-rate-attachment fragment shading rate attachment> -- /must/ be greater than or equal to ⌈@width@ \/ @texelWidth@⌉, where -- @texelWidth@ is the largest value of -- @shadingRateAttachmentTexelSize.width@ in a -- 'Vulkan.Extensions.VK_KHR_fragment_shading_rate.FragmentShadingRateAttachmentInfoKHR' -- which references that attachment -- -- - #VUID-VkFramebufferCreateInfo-flags-04544# If @flags@ includes -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT', -- the @height@ member of any element of the @pAttachmentImageInfos@ -- member of a -- 'Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer.FramebufferAttachmentsCreateInfo' -- structure in the @pNext@ chain that is used as a -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#primsrast-fragment-shading-rate-attachment fragment shading rate attachment> -- /must/ be greater than or equal to ⌈@height@ \/ @texelHeight@⌉, -- where @texelHeight@ is the largest value of -- @shadingRateAttachmentTexelSize.height@ in a -- 'Vulkan.Extensions.VK_KHR_fragment_shading_rate.FragmentShadingRateAttachmentInfoKHR' -- which references that attachment -- -- - #VUID-VkFramebufferCreateInfo-flags-04545# If @flags@ includes -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT', -- the @layerCount@ member of any element of the -- @pAttachmentImageInfos@ member of a -- 'Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer.FramebufferAttachmentsCreateInfo' -- structure in the @pNext@ chain that is used as a -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#primsrast-fragment-shading-rate-attachment fragment shading rate attachment> -- /must/ be either @1@, or greater than or equal to @layers@ -- -- - #VUID-VkFramebufferCreateInfo-flags-04587# If @flags@ includes -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT' -- and @renderPass@ was specified with non-zero view masks, each -- element of @pAttachments@ that is used as a -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#primsrast-fragment-shading-rate-attachment fragment shading rate attachment> -- by @renderPass@ /must/ have a @layerCount@ that is either @1@, or -- greater than the index of the most significant bit set in any of -- those view masks -- -- - #VUID-VkFramebufferCreateInfo-renderPass-03198# If multiview is -- enabled for @renderPass@ and @flags@ includes -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT', -- the @layerCount@ member of any element of the -- @pAttachmentImageInfos@ member of a -- 'Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer.FramebufferAttachmentsCreateInfo' -- structure included in the @pNext@ chain used as an input, color, -- resolve, or depth\/stencil attachment in @renderPass@ /must/ be -- greater than the maximum bit index set in the view mask in the -- subpasses in which it is used in @renderPass@ -- -- - #VUID-VkFramebufferCreateInfo-renderPass-04546# If multiview is not -- enabled for @renderPass@ and @flags@ includes -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT', -- the @layerCount@ member of any element of the -- @pAttachmentImageInfos@ member of a -- 'Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer.FramebufferAttachmentsCreateInfo' -- structure included in the @pNext@ chain used as an input, color, -- resolve, or depth\/stencil attachment in @renderPass@ /must/ be -- greater than or equal to @layers@ -- -- - #VUID-VkFramebufferCreateInfo-flags-03201# If @flags@ includes -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT', -- the @usage@ member of any element of the @pAttachmentImageInfos@ -- member of a -- 'Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer.FramebufferAttachmentsCreateInfo' -- structure included in the @pNext@ chain that refers to an attachment -- used as a color attachment or resolve attachment by @renderPass@ -- /must/ include -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_COLOR_ATTACHMENT_BIT' -- -- - #VUID-VkFramebufferCreateInfo-flags-03202# If @flags@ includes -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT', -- the @usage@ member of any element of the @pAttachmentImageInfos@ -- member of a -- 'Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer.FramebufferAttachmentsCreateInfo' -- structure included in the @pNext@ chain that refers to an attachment -- used as a depth\/stencil attachment by @renderPass@ /must/ include -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_DEPTH_STENCIL_ATTACHMENT_BIT' -- -- - #VUID-VkFramebufferCreateInfo-flags-03203# If @flags@ includes -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT', -- the @usage@ member of any element of the @pAttachmentImageInfos@ -- member of a -- 'Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer.FramebufferAttachmentsCreateInfo' -- structure included in the @pNext@ chain that refers to an attachment -- used as a depth\/stencil resolve attachment by @renderPass@ /must/ -- include -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_DEPTH_STENCIL_ATTACHMENT_BIT' -- -- - #VUID-VkFramebufferCreateInfo-flags-03204# If @flags@ includes -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT', -- the @usage@ member of any element of the @pAttachmentImageInfos@ -- member of a -- 'Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer.FramebufferAttachmentsCreateInfo' -- structure included in the @pNext@ chain that refers to an attachment -- used as an input attachment by @renderPass@ /must/ include -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_INPUT_ATTACHMENT_BIT' -- -- - #VUID-VkFramebufferCreateInfo-flags-03205# If @flags@ includes -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT', -- at least one element of the @pViewFormats@ member of any element of -- the @pAttachmentImageInfos@ member of a -- 'Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer.FramebufferAttachmentsCreateInfo' -- structure included in the @pNext@ chain /must/ be equal to the -- corresponding value of 'AttachmentDescription'::@format@ used to -- create @renderPass@ -- -- - #VUID-VkFramebufferCreateInfo-flags-04113# If @flags@ does not -- include -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT', -- each element of @pAttachments@ /must/ have been created with -- 'Vulkan.Core10.ImageView.ImageViewCreateInfo'::@viewType@ not equal -- to 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_3D' -- -- - #VUID-VkFramebufferCreateInfo-flags-04548# If @flags@ does not -- include -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT', -- each element of @pAttachments@ that is used as a fragment shading -- rate attachment by @renderPass@ /must/ have been created with a -- @usage@ value including -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_FRAGMENT_SHADING_RATE_ATTACHMENT_BIT_KHR' -- -- - #VUID-VkFramebufferCreateInfo-flags-04549# If @flags@ includes -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT', -- the @usage@ member of any element of the @pAttachmentImageInfos@ -- member of a -- 'Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer.FramebufferAttachmentsCreateInfo' -- structure included in the @pNext@ chain that refers to an attachment -- used as a fragment shading rate attachment by @renderPass@ /must/ -- include -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_FRAGMENT_SHADING_RATE_ATTACHMENT_BIT_KHR' -- -- - #VUID-VkFramebufferCreateInfo-samples-06881# If -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#subpass-multisampledrendertosinglesampled multisampled-render-to-single-sampled> -- is enabled for any subpass, all color, depth\/stencil and input -- attachments used in that subpass which have -- 'AttachmentDescription'::@samples@ or -- 'Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2.AttachmentDescription2'::@samples@ -- equal to -- 'Vulkan.Core10.Enums.SampleCountFlagBits.SAMPLE_COUNT_1_BIT' /must/ -- have been created with -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_MULTISAMPLED_RENDER_TO_SINGLE_SAMPLED_BIT_EXT' -- in their 'Vulkan.Core10.Image.ImageCreateInfo'::@flags@ -- -- - #VUID-VkFramebufferCreateInfo-samples-07009# If -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#subpass-multisampledrendertosinglesampled multisampled-render-to-single-sampled> -- is enabled for any subpass, all color, depth\/stencil and input -- attachments used in that subpass which have -- 'AttachmentDescription'::@samples@ or -- 'Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2.AttachmentDescription2'::@samples@ -- equal to -- 'Vulkan.Core10.Enums.SampleCountFlagBits.SAMPLE_COUNT_1_BIT' /must/ -- have a format that supports the sample count specified in -- 'Vulkan.Extensions.VK_EXT_multisampled_render_to_single_sampled.MultisampledRenderToSingleSampledInfoEXT'::@rasterizationSamples@ -- -- - #VUID-VkFramebufferCreateInfo-nullColorAttachmentWithExternalFormatResolve-09349# -- If the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#limits-nullColorAttachmentWithExternalFormatResolve nullColorAttachmentWithExternalFormatResolve> -- is 'Vulkan.Core10.FundamentalTypes.FALSE', and @flags@ does not -- include -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT', -- the format of the color attachment for each subpass in @renderPass@ -- that includes an external format image as a resolve attachment -- /must/ have a format equal to the value of -- 'Vulkan.Extensions.VK_ANDROID_external_format_resolve.AndroidHardwareBufferFormatResolvePropertiesANDROID'::@colorAttachmentFormat@ -- as returned by a call to -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.getAndroidHardwareBufferPropertiesANDROID' -- for the Android hardware buffer that was used to create the image -- view use as its resolve attachment -- -- - #VUID-VkFramebufferCreateInfo-pAttachments-09350# If @flags@ does -- not include -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT', -- then if an element of @pAttachments@ has a format of -- 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED', it /must/ have been -- created with a -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.ExternalFormatANDROID'::@externalFormat@ -- value identical to that provided in the -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.ExternalFormatANDROID'::@externalFormat@ -- specified by the corresponding -- 'Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2.AttachmentDescription2' -- in @renderPass@ -- -- == Valid Usage (Implicit) -- -- - #VUID-VkFramebufferCreateInfo-sType-sType# @sType@ /must/ be -- 'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_FRAMEBUFFER_CREATE_INFO' -- -- - #VUID-VkFramebufferCreateInfo-pNext-pNext# @pNext@ /must/ be @NULL@ -- or a pointer to a valid instance of -- 'Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer.FramebufferAttachmentsCreateInfo' -- -- - #VUID-VkFramebufferCreateInfo-sType-unique# The @sType@ value of -- each struct in the @pNext@ chain /must/ be unique -- -- - #VUID-VkFramebufferCreateInfo-flags-parameter# @flags@ /must/ be a -- valid combination of -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FramebufferCreateFlagBits' -- values -- -- - #VUID-VkFramebufferCreateInfo-renderPass-parameter# @renderPass@ -- /must/ be a valid 'Vulkan.Core10.Handles.RenderPass' handle -- -- - #VUID-VkFramebufferCreateInfo-commonparent# Both of @renderPass@, -- and the elements of @pAttachments@ that are valid handles of -- non-ignored parameters /must/ have been created, allocated, or -- retrieved from the same 'Vulkan.Core10.Handles.Device' -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FramebufferCreateFlags', -- 'Vulkan.Core10.Handles.ImageView', 'Vulkan.Core10.Handles.RenderPass', -- 'Vulkan.Core10.Enums.StructureType.StructureType', 'createFramebuffer' data FramebufferCreateInfo (es :: [Type]) = FramebufferCreateInfo { -- | @pNext@ is @NULL@ or a pointer to a structure extending this structure. forall (es :: [*]). FramebufferCreateInfo es -> Chain es next :: Chain es , -- | @flags@ is a bitmask of -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FramebufferCreateFlagBits' forall (es :: [*]). FramebufferCreateInfo es -> FramebufferCreateFlags flags :: FramebufferCreateFlags , -- | @renderPass@ is a render pass defining what render passes the -- framebuffer will be compatible with. See -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#renderpass-compatibility Render Pass Compatibility> -- for details. forall (es :: [*]). FramebufferCreateInfo es -> RenderPass renderPass :: RenderPass , -- | @pAttachments@ is a pointer to an array of -- 'Vulkan.Core10.Handles.ImageView' handles, each of which will be used as -- the corresponding attachment in a render pass instance. If @flags@ -- includes -- 'Vulkan.Core10.Enums.FramebufferCreateFlagBits.FRAMEBUFFER_CREATE_IMAGELESS_BIT', -- this parameter is ignored. forall (es :: [*]). FramebufferCreateInfo es -> Vector ImageView attachments :: Vector ImageView , -- | @width@, @height@ and @layers@ define the dimensions of the framebuffer. -- If the render pass uses multiview, then @layers@ /must/ be one and each -- attachment requires a number of layers that is greater than the maximum -- bit index set in the view mask in the subpasses in which it is used. forall (es :: [*]). FramebufferCreateInfo es -> Word32 width :: Word32 , -- No documentation found for Nested "VkFramebufferCreateInfo" "height" forall (es :: [*]). FramebufferCreateInfo es -> Word32 height :: Word32 , -- No documentation found for Nested "VkFramebufferCreateInfo" "layers" forall (es :: [*]). FramebufferCreateInfo es -> Word32 layers :: Word32 } deriving (Typeable) #if defined(GENERIC_INSTANCES) deriving instance Generic (FramebufferCreateInfo (es :: [Type])) #endif deriving instance Show (Chain es) => Show (FramebufferCreateInfo es) instance Extensible FramebufferCreateInfo where extensibleTypeName :: String extensibleTypeName = String "FramebufferCreateInfo" setNext :: forall (ds :: [*]) (es :: [*]). FramebufferCreateInfo ds -> Chain es -> FramebufferCreateInfo es setNext FramebufferCreateInfo{Word32 Vector ImageView Chain ds RenderPass FramebufferCreateFlags layers :: Word32 height :: Word32 width :: Word32 attachments :: Vector ImageView renderPass :: RenderPass flags :: FramebufferCreateFlags next :: Chain ds $sel:layers:FramebufferCreateInfo :: forall (es :: [*]). FramebufferCreateInfo es -> Word32 $sel:height:FramebufferCreateInfo :: forall (es :: [*]). FramebufferCreateInfo es -> Word32 $sel:width:FramebufferCreateInfo :: forall (es :: [*]). FramebufferCreateInfo es -> Word32 $sel:attachments:FramebufferCreateInfo :: forall (es :: [*]). FramebufferCreateInfo es -> Vector ImageView $sel:renderPass:FramebufferCreateInfo :: forall (es :: [*]). FramebufferCreateInfo es -> RenderPass $sel:flags:FramebufferCreateInfo :: forall (es :: [*]). FramebufferCreateInfo es -> FramebufferCreateFlags $sel:next:FramebufferCreateInfo :: forall (es :: [*]). FramebufferCreateInfo es -> Chain es ..} Chain es next' = FramebufferCreateInfo{$sel:next:FramebufferCreateInfo :: Chain es next = Chain es next', Word32 Vector ImageView RenderPass FramebufferCreateFlags layers :: Word32 height :: Word32 width :: Word32 attachments :: Vector ImageView renderPass :: RenderPass flags :: FramebufferCreateFlags $sel:layers:FramebufferCreateInfo :: Word32 $sel:height:FramebufferCreateInfo :: Word32 $sel:width:FramebufferCreateInfo :: Word32 $sel:attachments:FramebufferCreateInfo :: Vector ImageView $sel:renderPass:FramebufferCreateInfo :: RenderPass $sel:flags:FramebufferCreateInfo :: FramebufferCreateFlags ..} getNext :: forall (es :: [*]). FramebufferCreateInfo es -> Chain es getNext FramebufferCreateInfo{Word32 Vector ImageView Chain es RenderPass FramebufferCreateFlags layers :: Word32 height :: Word32 width :: Word32 attachments :: Vector ImageView renderPass :: RenderPass flags :: FramebufferCreateFlags next :: Chain es $sel:layers:FramebufferCreateInfo :: forall (es :: [*]). FramebufferCreateInfo es -> Word32 $sel:height:FramebufferCreateInfo :: forall (es :: [*]). FramebufferCreateInfo es -> Word32 $sel:width:FramebufferCreateInfo :: forall (es :: [*]). FramebufferCreateInfo es -> Word32 $sel:attachments:FramebufferCreateInfo :: forall (es :: [*]). FramebufferCreateInfo es -> Vector ImageView $sel:renderPass:FramebufferCreateInfo :: forall (es :: [*]). FramebufferCreateInfo es -> RenderPass $sel:flags:FramebufferCreateInfo :: forall (es :: [*]). FramebufferCreateInfo es -> FramebufferCreateFlags $sel:next:FramebufferCreateInfo :: forall (es :: [*]). FramebufferCreateInfo es -> Chain es ..} = Chain es next extends :: forall e b proxy. Typeable e => proxy e -> (Extends FramebufferCreateInfo e => b) -> Maybe b extends :: forall e b (proxy :: * -> *). Typeable e => proxy e -> (Extends FramebufferCreateInfo e => b) -> Maybe b extends proxy e _ Extends FramebufferCreateInfo e => b f | Just e :~: FramebufferAttachmentsCreateInfo Refl <- forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => Maybe (a :~: b) eqT @e @FramebufferAttachmentsCreateInfo = forall a. a -> Maybe a Just Extends FramebufferCreateInfo e => b f | Bool otherwise = forall a. Maybe a Nothing instance ( Extendss FramebufferCreateInfo es , PokeChain es ) => ToCStruct (FramebufferCreateInfo es) where withCStruct :: forall b. FramebufferCreateInfo es -> (Ptr (FramebufferCreateInfo es) -> IO b) -> IO b withCStruct FramebufferCreateInfo es x Ptr (FramebufferCreateInfo es) -> IO b f = forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes Int 64 forall a b. (a -> b) -> a -> b $ \Ptr (FramebufferCreateInfo es) p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b pokeCStruct Ptr (FramebufferCreateInfo es) p FramebufferCreateInfo es x (Ptr (FramebufferCreateInfo es) -> IO b f Ptr (FramebufferCreateInfo es) p) pokeCStruct :: forall b. Ptr (FramebufferCreateInfo es) -> FramebufferCreateInfo es -> IO b -> IO b pokeCStruct Ptr (FramebufferCreateInfo es) p FramebufferCreateInfo{Word32 Vector ImageView Chain es RenderPass FramebufferCreateFlags layers :: Word32 height :: Word32 width :: Word32 attachments :: Vector ImageView renderPass :: RenderPass flags :: FramebufferCreateFlags next :: Chain es $sel:layers:FramebufferCreateInfo :: forall (es :: [*]). FramebufferCreateInfo es -> Word32 $sel:height:FramebufferCreateInfo :: forall (es :: [*]). FramebufferCreateInfo es -> Word32 $sel:width:FramebufferCreateInfo :: forall (es :: [*]). FramebufferCreateInfo es -> Word32 $sel:attachments:FramebufferCreateInfo :: forall (es :: [*]). FramebufferCreateInfo es -> Vector ImageView $sel:renderPass:FramebufferCreateInfo :: forall (es :: [*]). FramebufferCreateInfo es -> RenderPass $sel:flags:FramebufferCreateInfo :: forall (es :: [*]). FramebufferCreateInfo es -> FramebufferCreateFlags $sel:next:FramebufferCreateInfo :: forall (es :: [*]). FramebufferCreateInfo es -> Chain es ..} IO b f = forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT forall a b. (a -> b) -> a -> b $ do forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (FramebufferCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr StructureType)) (StructureType STRUCTURE_TYPE_FRAMEBUFFER_CREATE_INFO) Ptr () pNext'' <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap forall a b. Ptr a -> Ptr b castPtr forall b c a. (b -> c) -> (a -> b) -> a -> c . forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall (es :: [*]) a. PokeChain es => Chain es -> (Ptr (Chain es) -> IO a) -> IO a withChain (Chain es next) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (FramebufferCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr (Ptr ()))) Ptr () pNext'' forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (FramebufferCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr FramebufferCreateFlags)) (FramebufferCreateFlags flags) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (FramebufferCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 24 :: Ptr RenderPass)) (RenderPass renderPass) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (FramebufferCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 32 :: Ptr Word32)) ((forall a b. (Integral a, Num b) => a -> b fromIntegral (forall a. Vector a -> Int Data.Vector.length forall a b. (a -> b) -> a -> b $ (Vector ImageView attachments)) :: Word32)) Ptr ImageView pPAttachments' <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes @ImageView ((forall a. Vector a -> Int Data.Vector.length (Vector ImageView attachments)) forall a. Num a => a -> a -> a * Int 8) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\Int i ImageView e -> forall a. Storable a => Ptr a -> a -> IO () poke (Ptr ImageView pPAttachments' forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 8 forall a. Num a => a -> a -> a * (Int i)) :: Ptr ImageView) (ImageView e)) (Vector ImageView attachments) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (FramebufferCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 40 :: Ptr (Ptr ImageView))) (Ptr ImageView pPAttachments') forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (FramebufferCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 48 :: Ptr Word32)) (Word32 width) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (FramebufferCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 52 :: Ptr Word32)) (Word32 height) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (FramebufferCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 56 :: Ptr Word32)) (Word32 layers) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ IO b f cStructSize :: Int cStructSize = Int 64 cStructAlignment :: Int cStructAlignment = Int 8 pokeZeroCStruct :: forall b. Ptr (FramebufferCreateInfo es) -> IO b -> IO b pokeZeroCStruct Ptr (FramebufferCreateInfo es) p IO b f = forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT forall a b. (a -> b) -> a -> b $ do forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (FramebufferCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr StructureType)) (StructureType STRUCTURE_TYPE_FRAMEBUFFER_CREATE_INFO) Ptr () pNext' <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap forall a b. Ptr a -> Ptr b castPtr forall b c a. (b -> c) -> (a -> b) -> a -> c . forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall (es :: [*]) a. PokeChain es => (Ptr (Chain es) -> IO a) -> IO a withZeroChain @es forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (FramebufferCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr (Ptr ()))) Ptr () pNext' forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (FramebufferCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 24 :: Ptr RenderPass)) (forall a. Zero a => a zero) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (FramebufferCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 48 :: Ptr Word32)) (forall a. Zero a => a zero) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (FramebufferCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 52 :: Ptr Word32)) (forall a. Zero a => a zero) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr (FramebufferCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 56 :: Ptr Word32)) (forall a. Zero a => a zero) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ IO b f instance ( Extendss FramebufferCreateInfo es , PeekChain es ) => FromCStruct (FramebufferCreateInfo es) where peekCStruct :: Ptr (FramebufferCreateInfo es) -> IO (FramebufferCreateInfo es) peekCStruct Ptr (FramebufferCreateInfo es) p = do Ptr () pNext <- forall a. Storable a => Ptr a -> IO a peek @(Ptr ()) ((Ptr (FramebufferCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr (Ptr ()))) Chain es next <- forall (es :: [*]). PeekChain es => Ptr (Chain es) -> IO (Chain es) peekChain (forall a b. Ptr a -> Ptr b castPtr Ptr () pNext) FramebufferCreateFlags flags <- forall a. Storable a => Ptr a -> IO a peek @FramebufferCreateFlags ((Ptr (FramebufferCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr FramebufferCreateFlags)) RenderPass renderPass <- forall a. Storable a => Ptr a -> IO a peek @RenderPass ((Ptr (FramebufferCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 24 :: Ptr RenderPass)) Word32 attachmentCount <- forall a. Storable a => Ptr a -> IO a peek @Word32 ((Ptr (FramebufferCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 32 :: Ptr Word32)) Ptr ImageView pAttachments <- forall a. Storable a => Ptr a -> IO a peek @(Ptr ImageView) ((Ptr (FramebufferCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 40 :: Ptr (Ptr ImageView))) Vector ImageView pAttachments' <- forall (m :: * -> *) a. Monad m => Int -> (Int -> m a) -> m (Vector a) generateM (forall a b. (Integral a, Num b) => a -> b fromIntegral Word32 attachmentCount) (\Int i -> forall a. Storable a => Ptr a -> IO a peek @ImageView ((Ptr ImageView pAttachments forall a. Ptr a -> Int -> Ptr a `advancePtrBytes` (Int 8 forall a. Num a => a -> a -> a * (Int i)) :: Ptr ImageView))) Word32 width <- forall a. Storable a => Ptr a -> IO a peek @Word32 ((Ptr (FramebufferCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 48 :: Ptr Word32)) Word32 height <- forall a. Storable a => Ptr a -> IO a peek @Word32 ((Ptr (FramebufferCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 52 :: Ptr Word32)) Word32 layers <- forall a. Storable a => Ptr a -> IO a peek @Word32 ((Ptr (FramebufferCreateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 56 :: Ptr Word32)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ forall (es :: [*]). Chain es -> FramebufferCreateFlags -> RenderPass -> Vector ImageView -> Word32 -> Word32 -> Word32 -> FramebufferCreateInfo es FramebufferCreateInfo Chain es next FramebufferCreateFlags flags RenderPass renderPass Vector ImageView pAttachments' Word32 width Word32 height Word32 layers instance es ~ '[] => Zero (FramebufferCreateInfo es) where zero :: FramebufferCreateInfo es zero = forall (es :: [*]). Chain es -> FramebufferCreateFlags -> RenderPass -> Vector ImageView -> Word32 -> Word32 -> Word32 -> FramebufferCreateInfo es FramebufferCreateInfo () forall a. Zero a => a zero forall a. Zero a => a zero forall a. Monoid a => a mempty forall a. Zero a => a zero forall a. Zero a => a zero forall a. Zero a => a zero