module Render.ForwardMsaa
( ForwardMsaa(..)
, allocateMsaa
, updateMsaa
, usePass
) where
import RIO
import Control.Monad.Trans.Resource qualified as Resource
import Data.Bits ((.|.))
import Data.Vector qualified as Vector
import Vulkan.Core10 qualified as Vk
import Vulkan.Zero (zero)
import Engine.Types.RefCounted (RefCounted, releaseRefCounted, resourceTRefCount)
import Engine.Types.RefCounted qualified as RefCounted
import Engine.Vulkan.Types (HasVulkan(..), HasSwapchain(..), HasRenderPass(..), RenderPass(..), MonadVulkan)
import Render.Pass (usePass)
import Resource.Image (AllocatedImage)
import Resource.Image qualified as Image
import Resource.Region qualified as Region
import Resource.Vulkan.Named qualified as Named
data ForwardMsaa = ForwardMsaa
{ ForwardMsaa -> RenderPass
fmRenderPass :: Vk.RenderPass
, ForwardMsaa -> AllocatedImage
fmColor :: AllocatedImage
, ForwardMsaa -> AllocatedImage
fmDepth :: AllocatedImage
, ForwardMsaa -> Vector Framebuffer
fmFrameBuffers :: Vector Vk.Framebuffer
, ForwardMsaa -> Rect2D
fmRenderArea :: Vk.Rect2D
, ForwardMsaa -> Vector ClearValue
fmClear :: Vector Vk.ClearValue
, ForwardMsaa -> RefCounted
fmRelease :: RefCounted
}
instance HasRenderPass ForwardMsaa where
getRenderPass :: ForwardMsaa -> RenderPass
getRenderPass = ForwardMsaa -> RenderPass
fmRenderPass
getFramebuffers :: ForwardMsaa -> Vector Framebuffer
getFramebuffers = ForwardMsaa -> Vector Framebuffer
fmFrameBuffers
getClearValues :: ForwardMsaa -> Vector ClearValue
getClearValues = ForwardMsaa -> Vector ClearValue
fmClear
getRenderArea :: ForwardMsaa -> Rect2D
getRenderArea = ForwardMsaa -> Rect2D
fmRenderArea
instance RenderPass ForwardMsaa where
updateRenderpass :: forall env swapchain.
(HasLogFunc env, HasSwapchain swapchain, HasVulkan env,
MonadResource (RIO env)) =>
swapchain -> ForwardMsaa -> RIO env ForwardMsaa
updateRenderpass = forall (m :: * -> *) env swapchain.
(MonadResource m, MonadVulkan env m, HasLogFunc env,
HasSwapchain swapchain) =>
swapchain -> ForwardMsaa -> m ForwardMsaa
updateMsaa
refcountRenderpass :: forall env. MonadResource (RIO env) => ForwardMsaa -> RIO env ()
refcountRenderpass = forall (f :: * -> *). MonadResource f => RefCounted -> f ()
resourceTRefCount forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForwardMsaa -> RefCounted
fmRelease
allocateMsaa
:: ( Resource.MonadResource m
, MonadVulkan env m
, HasLogFunc env
, HasSwapchain swapchain
)
=> swapchain
-> m ForwardMsaa
allocateMsaa :: forall (m :: * -> *) env swapchain.
(MonadResource m, MonadVulkan env m, HasLogFunc env,
HasSwapchain swapchain) =>
swapchain -> m ForwardMsaa
allocateMsaa swapchain
swapchain = do
(ReleaseKey
_rpKey, RenderPass
renderPass) <- forall env (m :: * -> *) swapchain.
(MonadVulkan env m, MonadResource m, HasSwapchain swapchain) =>
swapchain -> m (ReleaseKey, RenderPass)
allocateRenderPassMsaa swapchain
swapchain
(RefCounted
release, FramebuffersMsaa
resources) <- forall (m :: * -> *) a.
MonadResource m =>
m (ReleaseKey, a) -> m (RefCounted, a)
RefCounted.wrapped forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a.
MonadResource m =>
ResourceT m a -> m (ReleaseKey, a)
Region.run do
forall (m :: * -> *) env.
(MonadUnliftIO m, MonadReader env m, HasLogFunc env,
HasCallStack) =>
Utf8Builder -> Utf8Builder -> ResourceT m ()
Region.logDebug
Utf8Builder
"Allocating ForwardMsaa resources"
Utf8Builder
"Releasing ForwardMsaa resources"
forall (m :: * -> *) env swapchain.
(MonadResource m, MonadVulkan env m, HasSwapchain swapchain) =>
swapchain -> RenderPass -> m FramebuffersMsaa
allocateFramebufferMsaa swapchain
swapchain RenderPass
renderPass
let (AllocatedImage
color, AllocatedImage
depth, Vector Framebuffer
framebuffers) = FramebuffersMsaa
resources
forall (f :: * -> *) a. Applicative f => a -> f a
pure ForwardMsaa
{ $sel:fmRenderPass:ForwardMsaa :: RenderPass
fmRenderPass = RenderPass
renderPass
, $sel:fmRenderArea:ForwardMsaa :: Rect2D
fmRenderArea = Rect2D
fullSurface
, $sel:fmClear:ForwardMsaa :: Vector ClearValue
fmClear = Vector ClearValue
clear
, $sel:fmColor:ForwardMsaa :: AllocatedImage
fmColor = AllocatedImage
color
, $sel:fmDepth:ForwardMsaa :: AllocatedImage
fmDepth = AllocatedImage
depth
, $sel:fmFrameBuffers:ForwardMsaa :: Vector Framebuffer
fmFrameBuffers = Vector Framebuffer
framebuffers
, $sel:fmRelease:ForwardMsaa :: RefCounted
fmRelease = RefCounted
release
}
where
fullSurface :: Rect2D
fullSurface = Vk.Rect2D
{ $sel:offset:Rect2D :: Offset2D
Vk.offset = forall a. Zero a => a
zero
, $sel:extent:Rect2D :: Extent2D
Vk.extent = forall a. HasSwapchain a => a -> Extent2D
getSurfaceExtent swapchain
swapchain
}
clear :: Vector ClearValue
clear = forall a. [a] -> Vector a
Vector.fromList
[ ClearValue
clearColor
, ClearDepthStencilValue -> ClearValue
Vk.DepthStencil (Float -> Word32 -> ClearDepthStencilValue
Vk.ClearDepthStencilValue Float
1.0 Word32
0)
, ClearValue
clearColor
]
clearColor :: ClearValue
clearColor = ClearColorValue -> ClearValue
Vk.Color forall a. Zero a => a
zero
updateMsaa
:: ( Resource.MonadResource m
, MonadVulkan env m
, HasLogFunc env
, HasSwapchain swapchain
)
=> swapchain
-> ForwardMsaa
-> m ForwardMsaa
updateMsaa :: forall (m :: * -> *) env swapchain.
(MonadResource m, MonadVulkan env m, HasLogFunc env,
HasSwapchain swapchain) =>
swapchain -> ForwardMsaa -> m ForwardMsaa
updateMsaa swapchain
swapchain old :: ForwardMsaa
old@ForwardMsaa{RefCounted
fmRelease :: RefCounted
$sel:fmRelease:ForwardMsaa :: ForwardMsaa -> RefCounted
fmRelease, RenderPass
fmRenderPass :: RenderPass
$sel:fmRenderPass:ForwardMsaa :: ForwardMsaa -> RenderPass
fmRenderPass} = do
forall (m :: * -> *). MonadIO m => RefCounted -> m ()
releaseRefCounted RefCounted
fmRelease
(RefCounted
release, FramebuffersMsaa
resources) <- forall (m :: * -> *) a.
MonadResource m =>
m (ReleaseKey, a) -> m (RefCounted, a)
RefCounted.wrapped forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a.
MonadResource m =>
ResourceT m a -> m (ReleaseKey, a)
Region.run do
forall (m :: * -> *) env.
(MonadUnliftIO m, MonadReader env m, HasLogFunc env,
HasCallStack) =>
Utf8Builder -> Utf8Builder -> ResourceT m ()
Region.logDebug
Utf8Builder
"Updating ForwardMsaa resources"
Utf8Builder
"Releasing ForwardMsaa resources"
forall (m :: * -> *) env swapchain.
(MonadResource m, MonadVulkan env m, HasSwapchain swapchain) =>
swapchain -> RenderPass -> m FramebuffersMsaa
allocateFramebufferMsaa swapchain
swapchain RenderPass
fmRenderPass
let (AllocatedImage
color, AllocatedImage
depth, Vector Framebuffer
framebuffers) = FramebuffersMsaa
resources
pure ForwardMsaa
old
{ $sel:fmColor:ForwardMsaa :: AllocatedImage
fmColor = AllocatedImage
color
, $sel:fmDepth:ForwardMsaa :: AllocatedImage
fmDepth = AllocatedImage
depth
, $sel:fmFrameBuffers:ForwardMsaa :: Vector Framebuffer
fmFrameBuffers = Vector Framebuffer
framebuffers
, $sel:fmRelease:ForwardMsaa :: RefCounted
fmRelease = RefCounted
release
, $sel:fmRenderArea:ForwardMsaa :: Rect2D
fmRenderArea = Rect2D
fullSurface
}
where
fullSurface :: Rect2D
fullSurface = Vk.Rect2D
{ $sel:offset:Rect2D :: Offset2D
Vk.offset = forall a. Zero a => a
zero
, $sel:extent:Rect2D :: Extent2D
Vk.extent = forall a. HasSwapchain a => a -> Extent2D
getSurfaceExtent swapchain
swapchain
}
allocateRenderPassMsaa
:: ( MonadVulkan env m
, Resource.MonadResource m
, HasSwapchain swapchain
)
=> swapchain
-> m (Resource.ReleaseKey, Vk.RenderPass)
allocateRenderPassMsaa :: forall env (m :: * -> *) swapchain.
(MonadVulkan env m, MonadResource m, HasSwapchain swapchain) =>
swapchain -> m (ReleaseKey, RenderPass)
allocateRenderPassMsaa swapchain
swapchain = do
Device
device <- forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks forall a. HasVulkan a => a -> Device
getDevice
(ReleaseKey, RenderPass)
res <- forall (a :: [*]) (io :: * -> *) r.
(Extendss RenderPassCreateInfo a, PokeChain a, MonadIO io) =>
Device
-> RenderPassCreateInfo a
-> Maybe AllocationCallbacks
-> (io RenderPass -> (RenderPass -> io ()) -> r)
-> r
Vk.withRenderPass Device
device RenderPassCreateInfo '[]
createInfo forall a. Maybe a
Nothing forall (m :: * -> *) a.
MonadResource m =>
IO a -> (a -> IO ()) -> m (ReleaseKey, a)
Resource.allocate
forall env (m :: * -> *) a.
(MonadVulkan env m, HasObjectType a) =>
a -> Text -> m ()
Named.object (forall a b. (a, b) -> b
snd (ReleaseKey, RenderPass)
res) Text
"ForwardMSAA"
pure (ReleaseKey, RenderPass)
res
where
format :: Format
format = forall a. HasSwapchain a => a -> Format
getSurfaceFormat swapchain
swapchain
depthFormat :: Format
depthFormat = forall a. HasSwapchain a => a -> Format
getDepthFormat swapchain
swapchain
msaa :: SampleCountFlagBits
msaa = forall a. HasSwapchain a => a -> SampleCountFlagBits
getMultisample swapchain
swapchain
onMsaa :: a -> a -> a
onMsaa :: forall a. a -> a -> a
onMsaa a
none a
more = case SampleCountFlagBits
msaa of
SampleCountFlagBits
Vk.SAMPLE_COUNT_1_BIT ->
a
none
SampleCountFlagBits
_mucho ->
a
more
attachments :: [AttachmentDescription]
attachments =
AttachmentDescription
color forall a. a -> [a] -> [a]
:
AttachmentDescription
depth forall a. a -> [a] -> [a]
:
forall a. a -> a -> a
onMsaa [] [AttachmentDescription
colorResolve]
createInfo :: RenderPassCreateInfo '[]
createInfo = forall a. Zero a => a
zero
{ $sel:attachments:RenderPassCreateInfo :: Vector AttachmentDescription
Vk.attachments = forall a. [a] -> Vector a
Vector.fromList [AttachmentDescription]
attachments
, $sel:subpasses:RenderPassCreateInfo :: Vector SubpassDescription
Vk.subpasses = forall a. [a] -> Vector a
Vector.fromList [SubpassDescription
subpass]
, $sel:dependencies:RenderPassCreateInfo :: Vector SubpassDependency
Vk.dependencies = forall a. [a] -> Vector a
Vector.fromList [SubpassDependency
colorDeps, SubpassDependency
depthDeps]
}
color :: AttachmentDescription
color = forall a. Zero a => a
zero
{ $sel:format:AttachmentDescription :: Format
Vk.format = Format
format
, $sel:samples:AttachmentDescription :: SampleCountFlagBits
Vk.samples = SampleCountFlagBits
msaa
, $sel:finalLayout:AttachmentDescription :: ImageLayout
Vk.finalLayout = ImageLayout
finalColorLayout
, $sel:loadOp:AttachmentDescription :: AttachmentLoadOp
Vk.loadOp = AttachmentLoadOp
Vk.ATTACHMENT_LOAD_OP_CLEAR
, $sel:storeOp:AttachmentDescription :: AttachmentStoreOp
Vk.storeOp = AttachmentStoreOp
Vk.ATTACHMENT_STORE_OP_DONT_CARE
, $sel:stencilLoadOp:AttachmentDescription :: AttachmentLoadOp
Vk.stencilLoadOp = AttachmentLoadOp
Vk.ATTACHMENT_LOAD_OP_DONT_CARE
, $sel:stencilStoreOp:AttachmentDescription :: AttachmentStoreOp
Vk.stencilStoreOp = AttachmentStoreOp
Vk.ATTACHMENT_STORE_OP_DONT_CARE
, $sel:initialLayout:AttachmentDescription :: ImageLayout
Vk.initialLayout = ImageLayout
Vk.IMAGE_LAYOUT_UNDEFINED
}
finalColorLayout :: ImageLayout
finalColorLayout =
forall a. a -> a -> a
onMsaa
ImageLayout
Vk.IMAGE_LAYOUT_PRESENT_SRC_KHR
ImageLayout
Vk.IMAGE_LAYOUT_COLOR_ATTACHMENT_OPTIMAL
depth :: AttachmentDescription
depth = forall a. Zero a => a
zero
{ $sel:format:AttachmentDescription :: Format
Vk.format = Format
depthFormat
, $sel:samples:AttachmentDescription :: SampleCountFlagBits
Vk.samples = SampleCountFlagBits
msaa
, $sel:loadOp:AttachmentDescription :: AttachmentLoadOp
Vk.loadOp = AttachmentLoadOp
Vk.ATTACHMENT_LOAD_OP_CLEAR
, $sel:storeOp:AttachmentDescription :: AttachmentStoreOp
Vk.storeOp = AttachmentStoreOp
Vk.ATTACHMENT_STORE_OP_DONT_CARE
, $sel:stencilLoadOp:AttachmentDescription :: AttachmentLoadOp
Vk.stencilLoadOp = AttachmentLoadOp
Vk.ATTACHMENT_LOAD_OP_DONT_CARE
, $sel:stencilStoreOp:AttachmentDescription :: AttachmentStoreOp
Vk.stencilStoreOp = AttachmentStoreOp
Vk.ATTACHMENT_STORE_OP_DONT_CARE
, $sel:initialLayout:AttachmentDescription :: ImageLayout
Vk.initialLayout = ImageLayout
Vk.IMAGE_LAYOUT_UNDEFINED
, $sel:finalLayout:AttachmentDescription :: ImageLayout
Vk.finalLayout = ImageLayout
Vk.IMAGE_LAYOUT_DEPTH_STENCIL_ATTACHMENT_OPTIMAL
}
colorResolve :: AttachmentDescription
colorResolve = forall a. Zero a => a
zero
{ $sel:format:AttachmentDescription :: Format
Vk.format = Format
format
, $sel:samples:AttachmentDescription :: SampleCountFlagBits
Vk.samples = SampleCountFlagBits
Vk.SAMPLE_COUNT_1_BIT
, $sel:finalLayout:AttachmentDescription :: ImageLayout
Vk.finalLayout = ImageLayout
Vk.IMAGE_LAYOUT_PRESENT_SRC_KHR
, $sel:loadOp:AttachmentDescription :: AttachmentLoadOp
Vk.loadOp = AttachmentLoadOp
Vk.ATTACHMENT_LOAD_OP_DONT_CARE
}
subpass :: SubpassDescription
subpass = forall a. Zero a => a
zero
{ $sel:pipelineBindPoint:SubpassDescription :: PipelineBindPoint
Vk.pipelineBindPoint = PipelineBindPoint
Vk.PIPELINE_BIND_POINT_GRAPHICS
, $sel:colorAttachments:SubpassDescription :: Vector AttachmentReference
Vk.colorAttachments = forall a. a -> Vector a
Vector.singleton forall a. Zero a => a
zero
{ $sel:attachment:AttachmentReference :: Word32
Vk.attachment = Word32
0
, $sel:layout:AttachmentReference :: ImageLayout
Vk.layout = ImageLayout
Vk.IMAGE_LAYOUT_COLOR_ATTACHMENT_OPTIMAL
}
, $sel:depthStencilAttachment:SubpassDescription :: Maybe AttachmentReference
Vk.depthStencilAttachment = forall a. a -> Maybe a
Just forall a. Zero a => a
zero
{ $sel:attachment:AttachmentReference :: Word32
Vk.attachment = Word32
1
, $sel:layout:AttachmentReference :: ImageLayout
Vk.layout = ImageLayout
Vk.IMAGE_LAYOUT_DEPTH_STENCIL_ATTACHMENT_OPTIMAL
}
, $sel:resolveAttachments:SubpassDescription :: Vector AttachmentReference
Vk.resolveAttachments =
forall a. a -> a -> a
onMsaa forall a. Monoid a => a
mempty forall a b. (a -> b) -> a -> b
$
forall a. a -> Vector a
Vector.singleton forall a. Zero a => a
zero
{ $sel:attachment:AttachmentReference :: Word32
Vk.attachment = Word32
2
, $sel:layout:AttachmentReference :: ImageLayout
Vk.layout = ImageLayout
Vk.IMAGE_LAYOUT_COLOR_ATTACHMENT_OPTIMAL
}
}
colorDeps :: SubpassDependency
colorDeps = forall a. Zero a => a
zero
{ $sel:srcSubpass:SubpassDependency :: Word32
Vk.srcSubpass = Word32
Vk.SUBPASS_EXTERNAL
, $sel:dstSubpass:SubpassDependency :: Word32
Vk.dstSubpass = Word32
0
, $sel:srcStageMask:SubpassDependency :: PipelineStageFlags
Vk.srcStageMask = PipelineStageFlags
colorOut
, $sel:srcAccessMask:SubpassDependency :: AccessFlags
Vk.srcAccessMask = forall a. Zero a => a
zero
, $sel:dstStageMask:SubpassDependency :: PipelineStageFlags
Vk.dstStageMask = PipelineStageFlags
colorOut
, $sel:dstAccessMask:SubpassDependency :: AccessFlags
Vk.dstAccessMask = AccessFlags
colorRW
}
where
colorOut :: PipelineStageFlags
colorOut =
PipelineStageFlags
Vk.PIPELINE_STAGE_COLOR_ATTACHMENT_OUTPUT_BIT
colorRW :: AccessFlags
colorRW =
AccessFlags
Vk.ACCESS_COLOR_ATTACHMENT_READ_BIT forall a. Bits a => a -> a -> a
.|.
AccessFlags
Vk.ACCESS_COLOR_ATTACHMENT_WRITE_BIT
depthDeps :: SubpassDependency
depthDeps = forall a. Zero a => a
zero
{ $sel:srcSubpass:SubpassDependency :: Word32
Vk.srcSubpass = Word32
Vk.SUBPASS_EXTERNAL
, $sel:dstSubpass:SubpassDependency :: Word32
Vk.dstSubpass = Word32
0
, $sel:srcStageMask:SubpassDependency :: PipelineStageFlags
Vk.srcStageMask = PipelineStageFlags
fragTests
, $sel:srcAccessMask:SubpassDependency :: AccessFlags
Vk.srcAccessMask = AccessFlags
depthW
, $sel:dstStageMask:SubpassDependency :: PipelineStageFlags
Vk.dstStageMask = PipelineStageFlags
fragTests
, $sel:dstAccessMask:SubpassDependency :: AccessFlags
Vk.dstAccessMask = AccessFlags
depthRW
}
where
fragTests :: PipelineStageFlags
fragTests =
PipelineStageFlags
Vk.PIPELINE_STAGE_EARLY_FRAGMENT_TESTS_BIT forall a. Bits a => a -> a -> a
.|.
PipelineStageFlags
Vk.PIPELINE_STAGE_LATE_FRAGMENT_TESTS_BIT
depthW :: AccessFlags
depthW =
AccessFlags
Vk.ACCESS_DEPTH_STENCIL_ATTACHMENT_WRITE_BIT
depthRW :: AccessFlags
depthRW =
AccessFlags
Vk.ACCESS_DEPTH_STENCIL_ATTACHMENT_READ_BIT forall a. Bits a => a -> a -> a
.|.
AccessFlags
depthW
type FramebuffersMsaa =
( Image.AllocatedImage
, Image.AllocatedImage
, Vector Vk.Framebuffer
)
allocateFramebufferMsaa
:: ( Resource.MonadResource m
, MonadVulkan env m
, HasSwapchain swapchain
)
=> swapchain
-> Vk.RenderPass
-> m FramebuffersMsaa
allocateFramebufferMsaa :: forall (m :: * -> *) env swapchain.
(MonadResource m, MonadVulkan env m, HasSwapchain swapchain) =>
swapchain -> RenderPass -> m FramebuffersMsaa
allocateFramebufferMsaa swapchain
swapchain RenderPass
renderPass = do
AllocatedImage
color <- forall env (io :: * -> *).
(MonadVulkan env io, MonadResource io) =>
Maybe Text
-> ImageAspectFlags
-> ("image dimensions" ::: Extent3D)
-> Word32
-> Word32
-> SampleCountFlagBits
-> Format
-> ImageUsageFlags
-> io AllocatedImage
Image.allocate
(forall a. a -> Maybe a
Just Text
"ForwardMSAA.color")
ImageAspectFlags
Vk.IMAGE_ASPECT_COLOR_BIT
(Extent2D -> Word32 -> "image dimensions" ::: Extent3D
Image.inflateExtent Extent2D
extent Word32
1)
Word32
1
Word32
1
(forall a. HasSwapchain a => a -> SampleCountFlagBits
getMultisample swapchain
swapchain)
(forall a. HasSwapchain a => a -> Format
getSurfaceFormat swapchain
swapchain)
ImageUsageFlags
Vk.IMAGE_USAGE_COLOR_ATTACHMENT_BIT
AllocatedImage
depth <- forall env (io :: * -> *).
(MonadVulkan env io, MonadResource io) =>
Maybe Text
-> ImageAspectFlags
-> ("image dimensions" ::: Extent3D)
-> Word32
-> Word32
-> SampleCountFlagBits
-> Format
-> ImageUsageFlags
-> io AllocatedImage
Image.allocate
(forall a. a -> Maybe a
Just Text
"ForwardMSAA.depth")
ImageAspectFlags
Vk.IMAGE_ASPECT_DEPTH_BIT
(Extent2D -> Word32 -> "image dimensions" ::: Extent3D
Image.inflateExtent Extent2D
extent Word32
1)
Word32
1
Word32
1
(forall a. HasSwapchain a => a -> SampleCountFlagBits
getMultisample swapchain
swapchain)
(forall a. HasSwapchain a => a -> Format
getDepthFormat swapchain
swapchain)
ImageUsageFlags
Vk.IMAGE_USAGE_DEPTH_STENCIL_ATTACHMENT_BIT
Vector Framebuffer
perView <- forall (m :: * -> *) a b.
Monad m =>
Vector a -> (Int -> a -> m b) -> m (Vector b)
Vector.iforM (forall a. HasSwapchain a => a -> Vector ImageView
getSwapchainViews swapchain
swapchain) \Int
ix ImageView
colorResolve -> do
let
attachments :: Vector ImageView
attachments = forall a. [a] -> Vector a
Vector.fromList
case forall a. HasSwapchain a => a -> SampleCountFlagBits
getMultisample swapchain
swapchain of
SampleCountFlagBits
Vk.SAMPLE_COUNT_1_BIT ->
[ ImageView
colorResolve
, AllocatedImage -> ImageView
Image.aiImageView AllocatedImage
depth
]
SampleCountFlagBits
_ ->
[ AllocatedImage -> ImageView
Image.aiImageView AllocatedImage
color
, AllocatedImage -> ImageView
Image.aiImageView AllocatedImage
depth
, ImageView
colorResolve
]
fbCI :: FramebufferCreateInfo '[]
fbCI = forall a. Zero a => a
zero
{ $sel:renderPass:FramebufferCreateInfo :: RenderPass
Vk.renderPass = RenderPass
renderPass
, $sel:width:FramebufferCreateInfo :: Word32
Vk.width = Word32
width
, $sel:height:FramebufferCreateInfo :: Word32
Vk.height = Word32
height
, $sel:attachments:FramebufferCreateInfo :: Vector ImageView
Vk.attachments = Vector ImageView
attachments
, $sel:layers:FramebufferCreateInfo :: Word32
Vk.layers = Word32
1
}
Device
device <- forall r (m :: * -> *) a. MonadReader r m => (r -> a) -> m a
asks forall a. HasVulkan a => a -> Device
getDevice
(ReleaseKey
_fbKey, Framebuffer
fb) <- forall (a :: [*]) (io :: * -> *) r.
(Extendss FramebufferCreateInfo a, PokeChain a, MonadIO io) =>
Device
-> FramebufferCreateInfo a
-> Maybe AllocationCallbacks
-> (io Framebuffer -> (Framebuffer -> io ()) -> r)
-> r
Vk.withFramebuffer Device
device FramebufferCreateInfo '[]
fbCI forall a. Maybe a
Nothing forall (m :: * -> *) a.
MonadResource m =>
IO a -> (a -> IO ()) -> m (ReleaseKey, a)
Resource.allocate
forall env (m :: * -> *) a.
(MonadVulkan env m, HasObjectType a) =>
a -> Text -> m ()
Named.object Framebuffer
fb forall a b. (a -> b) -> a -> b
$
Text
"ForwardMSAA.FB:" forall a. Semigroup a => a -> a -> a
<> forall a. IsString a => String -> a
fromString (forall a. Show a => a -> String
show @Int Int
ix)
pure Framebuffer
fb
pure (AllocatedImage
color, AllocatedImage
depth, Vector Framebuffer
perView)
where
extent :: Extent2D
extent@Vk.Extent2D{Word32
$sel:width:Extent2D :: Extent2D -> Word32
width :: Word32
width, Word32
$sel:height:Extent2D :: Extent2D -> Word32
height :: Word32
height} = forall a. HasSwapchain a => a -> Extent2D
getSurfaceExtent swapchain
swapchain