module Engine.Stage.Bootstrap.Setup ( stackStage , bootstrapStage ) where import RIO import Control.Monad.Trans.Resource (ResourceT) import UnliftIO.Resource qualified as Resource import Vulkan.Core10 qualified as Vk import Vulkan.NamedType ((:::)) import Engine.Types (StackStage(..), StageRIO, StageFrameRIO) import Engine.Types qualified as Engine import Engine.Vulkan.Types (Queues) import Engine.StageSwitch (trySwitchStage) import Engine.Stage.Bootstrap.Types (NoRendering(..), NoPipelines(..), NoResources(..), NoState(..)) stackStage :: (a -> StackStage) -> Engine.StageSetupRIO a -> StackStage stackStage handoff action = StackStage $ bootstrapStage handoff action bootstrapStage :: (a -> StackStage) -> Engine.StageSetupRIO a -> Engine.Stage NoRendering NoPipelines NoResources NoState bootstrapStage handoff action = Engine.Stage { sTitle = "Bootstrap" , sAllocateRP = noRendering , sAllocateP = noPipelines , sInitialRS = transitState handoff action , sInitialRR = noFrameResources , sBeforeLoop = pure () , sUpdateBuffers = noUpdates , sRecordCommands = noCommands , sAfterLoop = pure } noRendering :: swapchain -> ResourceT (StageRIO st) NoRendering noRendering _swapchain = pure NoRendering noPipelines :: swapchain -> NoRendering -> ResourceT (StageRIO st) NoPipelines noPipelines _swapchain NoRendering = pure NoPipelines noCommands :: Vk.CommandBuffer -> rd -> "image index" ::: Word32 -> StageFrameRIO rp p rd st () noCommands _cb _rd _index = pure () noUpdates :: st -> rd -> StageFrameRIO rp p rd st () noUpdates _st _rd = pure () transitState :: (a -> StackStage) -> Engine.StageSetupRIO a -> Engine.StageSetupRIO (Resource.ReleaseKey, NoState) transitState handoff action = do res <- action switched <- trySwitchStage . Engine.Replace $ handoff res unless switched $ logError "Bootstrap switch failed" key <- Resource.register $ pure () pure (key, NoState) noFrameResources :: Queues Vk.CommandPool -> renderPasses -> pipelines -> ResourceT (StageRIO rs) NoResources noFrameResources _queues _rp _p = fmap snd $! Resource.allocate (pure NoResources) (\NoResources -> pure ())