Skip to content

Commit

Permalink
Progress in Core compiling
Browse files Browse the repository at this point in the history
  • Loading branch information
alt-romes committed Oct 5, 2023
1 parent 5b0599d commit ec1c1b5
Show file tree
Hide file tree
Showing 10 changed files with 172 additions and 144 deletions.
2 changes: 2 additions & 0 deletions TODO
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
[ ] Implementar o ghengin-core/planets-core
[ ] A hie.yaml file to fix HLS?
[ ] Drop type parameter from RenderQueue
[ ] We only need the parameter to the render queue because we don't yet attach render properties to meshes
[ ] Add render properties to meshes
Expand Down
5 changes: 2 additions & 3 deletions ghengin-core-indep/ghengin-core-indep/Ghengin/Core/Prelude.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,7 @@ module Ghengin.Core.Prelude
, module Control.Monad.IO.Class.Linear
, module System.IO.Linear
, module Prelude
, module Data.Unrestricted.Linear.Orphans
-- , module Data.Unrestricted.Linear.Orphans

-- base
, Generic(..), NE.NonEmpty(..), Type, Constraint
Expand Down Expand Up @@ -56,7 +56,7 @@ import qualified Prelude

import Data.Tuple.Linear
import Data.Bifunctor.Linear (bimap)
import Data.Unrestricted.Linear.Orphans
import Data.Unrestricted.Linear.Orphans ()
import qualified Data.Functor.Linear as Data.Linear

import qualified Data.IntMap as IM
Expand All @@ -71,7 +71,6 @@ import GHC.Generics
import Data.Kind
import Data.Word
import Data.IORef (IORef)
import Data.Coerce

import Data.Unique (Unique)

Expand Down
213 changes: 112 additions & 101 deletions ghengin-core/ghengin-core/Ghengin/Core.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@ which one expresses more high-level game-engine and rendering abstractions, like
-}
module Ghengin.Core where

import qualified Prelude
import Ghengin.Core.Prelude
import Ghengin.Core.Log
import qualified Data.V.Linear as V
Expand All @@ -26,7 +27,7 @@ import Ghengin.Core.Mesh
import Ghengin.Core.Render.Property
import Ghengin.Core.Material

import Ghengin.Core.Type.Utils (nat)
import Ghengin.Core.Type.Utils

import qualified Data.Linear.Alias as Alias

Expand All @@ -48,38 +49,44 @@ newtype Core α = Core (StateT CoreState Renderer α)
runCore :: Core a IO a
runCore (Core st)
= runRenderer $ Linear.do
(a, CoreState i rq) <- runStateT st (CoreState 0 mempty)
flip evalStateT () $ traverseRenderQueue @(StateT () Renderer) @Renderer rq
(\pipeline _ -> Linear.do
-- lift $ destroyRenderPipeline p -- ROMES:TODO:
-- How do I return things if I am to destroy them??? likely make that
-- function yet more contrived. or simpler--really, we just need that
-- the thing is consumed in the function, hence the linear argument
-- (but if it is to be returned we must know, to enforce linearity? we'll see...)
return pipeline
)
(\p mat -> Linear.do
-- lift $ freeMaterial m -- ROMES:TODO:
return (p, mat)
)
(\p mesh () -> Linear.do
-- lift $ freeMesh m -- ROMES:TODO:
return (p, mesh)
)
(pure ())
(a, CoreState i (RenderQueue rq)) <- runStateT st (CoreState 0 (RenderQueue mempty))
-- TODO: FREE THINGS NEXT STEP!
Ur _ <- pure $ Unsafe.toLinear Ur rq
-- flip evalStateT () $ traverseRenderQueue @(StateT () Renderer) @Renderer rq
-- (\pipeline _ -> Linear.do
-- -- lift $ destroyRenderPipeline p -- ROMES:TODO:
-- -- How do I return things if I am to destroy them??? likely make that
-- -- function yet more contrived. or simpler--really, we just need that
-- -- the thing is consumed in the function, hence the linear argument
-- -- (but if it is to be returned we must know, to enforce linearity? we'll see...)
-- return pipeline
-- )
-- (\p mat -> Linear.do
-- -- lift $ freeMaterial m -- ROMES:TODO:
-- return (p, mat)
-- )
-- (\p mesh () -> Linear.do
-- -- lift $ freeMesh m -- ROMES:TODO:
-- return (p, mesh)
-- )
-- (pure ())
-- () <- pure (consume i)
-- return a
() <- pure (consume i)
return a



render :: Core ()
render = Core $ StateT $ \CoreState{..} -> enterD "render" $ do
render = Core $ StateT $ \CoreState{renderQueue= RenderQueue rqueue', frameCounter=fcounter'} -> enterD "render" $ Linear.do
Ur fcounter <- pure (move fcounter')
Ur unsafeQueue <- pure (Unsafe.toLinear Ur rqueue')

-- ROMES:TODO: This might cause flickering once every frame overflow due to ... overflows?
-- Need to consider what happens if it overflows. For now, good enough, it's
-- unlikely the frame count overflows, with 60 frames per second the game
-- would have to run for years to overflow a 64 bit integer
let frameIndex = frameCounter `mod` (nat @MAX_FRAMES_IN_FLIGHT_T)
let frameIndex = fcounter `mod` (nat @MAX_FRAMES_IN_FLIGHT_T)

-- Some required variables
-- TODO: instead, use defaults and provide functions to change viewport and scissor
Expand All @@ -98,7 +105,7 @@ render = Core $ StateT $ \CoreState{..} -> enterD "render" $ do
bind material descriptor set at set #1
∀ object that uses material do
bind object descriptor set at set #2
bind object model (vertex buffer)
draw object
Expand All @@ -125,67 +132,61 @@ render = Core $ StateT $ \CoreState{..} -> enterD "render" $ do
-- Now, render the renderable entities from the render queue in the given order.
-- If everything works as expected, if we blindly bind the descriptor sets as
-- they come, we should bind the pipeline once and each material once.
traverseRenderQueue @(CommandM Renderer) @(RenderPassCmdM Renderer)
renderQueue
-- Whenever we have a new pipeline, start its renderpass (lifting RenderPassCmd to Command)
(\pipeline next -> enterD "Traverse: pipeline" Linear.do

{-
We'll likely want to do some pre-processing of user-defined render passes,
but let's keep it simple and working for now.
-}

Ur rp' <- pure $ unsafeGetRenderPass pipeline
let rp = Unsafe.Alias.get rp' -- nice and unsafe
renderPassCmd currentImage rp extent $ Linear.do


-- then

pipesunit <- Data.traverse (Unsafe.toLinear \(Some2 @RenderPipeline @π @bs pipeline, materials) -> enterD "Traverse: pipeline" Linear.do

logT "Binding pipeline"
Ur graphicsPipeline <- pure $ completelyUnsafeGraphicsPipeline pipeline

-- The render pass for this pipeline has been bound already. Later on the render pass might not be necessarily coupled to the pipeline
-- Bind the pipeline
gppp' <- bindGraphicsPipeline graphicsPipeline
setViewport viewport
setScissor scissor

lift (descriptors pipeline) >>= \case-- TODO: Fix frames in flight... here it migth be crrect actylly, descriptor sets are shared, only one frame is being drawn at the time despite the double buffering
(dset, rmap, pipeline') -> Linear.do

-- These render properties are necessarily compatible with this
-- pipeline in the set #0, so the 'descriptorSetBinding' buffer
-- will always be valid to write with the corresponding
-- material binding
(rmap', pipeline'') <- lift $ Alias.useM rmap (\rmap' -> writePropertiesToResources rmap' pipeline')

-- Bind descriptor set #0
(dset', pLayout) <- Alias.useM dset (Unsafe.toLinear $ \dset' -> Linear.do
(pLayout', vkdset) <-
bindGraphicsDescriptorSet graphicsPipeline 0 dset'
pure (Unsafe.toLinear (\_ -> dset') vkdset, pLayout') --forget vulkan dset
)

-- Dangerous!! Could be forgetting values that need to be
-- reference-counted forgotten, or otherwise references become
-- obsolete. These values are probably shared before being
-- returned from 'descriptors' T_T.
-- OK, I made it less bad, now I'm only forgetting stuff I got unsafely...
-- And the pipeline T_T
Unsafe.toLinearN @3 (\_ _ _ -> pure ()) pipeline'' pLayout gppp' -- The pipeline is still in the Apecs store. Really, these functions should have no Unsafes and in that case all would be right (e.g. the resource passed to this function would have to be freed in this function, guaranteeing that it is reference counted or something?....

lift $ Linear.do
Alias.forget dset'
Alias.forget rmap'

-- finally, call the other actions in the renderpass cmd:
next
-- Whenever we have a new pipeline, start its renderpass (lifting RenderPassCmd to Command)

pure pipeline
)
(\pipeline material -> enterD "Material changed" Linear.do
{-
We'll likely want to do some pre-processing of user-defined render passes,
but let's keep it simple and working for now.
-}

Ur rp' <- pure $ unsafeGetRenderPass pipeline
let rp = Unsafe.Alias.get rp' -- nice and unsafe
renderPassCmd currentImage rp extent $ Linear.do

-- then

logT "Binding pipeline"
Ur graphicsPipeline <- pure $ completelyUnsafeGraphicsPipeline pipeline

-- The render pass for this pipeline has been bound already. Later on the render pass might not be necessarily coupled to the pipeline
-- Bind the pipeline
gppp' <- bindGraphicsPipeline graphicsPipeline
setViewport viewport
setScissor scissor

lift (descriptors pipeline) >>= \case
(dset, rmap, pipeline') -> Linear.do

-- These render properties are necessarily compatible with this
-- pipeline in the set #0, so the 'descriptorSetBinding' buffer
-- will always be valid to write with the corresponding
-- material binding
(rmap', pipeline'') <- lift $ Alias.useM rmap (\rmap' -> writePropertiesToResources rmap' pipeline')

-- Bind descriptor set #0
(dset', pLayout) <- Alias.useM dset (Unsafe.toLinear $ \dset' -> Linear.do
(pLayout', vkdset) <-
bindGraphicsDescriptorSet graphicsPipeline 0 dset'
pure (Unsafe.toLinear (\_ -> dset') vkdset, pLayout') --forget vulkan dset
)

-- Dangerous!! Could be forgetting values that need to be
-- reference-counted forgotten, or otherwise references become
-- obsolete. These values are probably shared before being
-- returned from 'descriptors' T_T.
-- OK, I made it less bad, now I'm only forgetting stuff I got unsafely...
-- And the pipeline T_T
Unsafe.toLinearN @3 (\_ _ _ -> pure ()) pipeline'' pLayout gppp' -- The pipeline is still in the Apecs store. Really, these functions should have no Unsafes and in that case all would be right (e.g. the resource passed to this function would have to be freed in this function, guaranteeing that it is reference counted or something?....

lift $ Linear.do
Alias.forget dset'
Alias.forget rmap'

-- For every material...
matsunits <- Data.traverse (Unsafe.toLinear \(Some @Material @ms material, meshes) -> enterD "Material changed" Linear.do

logT "Binding material..."
Ur graphicsPipeline <- pure $ completelyUnsafeGraphicsPipeline pipeline
Expand All @@ -212,36 +213,46 @@ render = Core $ StateT $ \CoreState{..} -> enterD "render" $ do
Alias.forget dset'
Alias.forget rmap'

pure (pipeline, material)
)
-- We used to have (\(SomePipeline pipeline) (Some mesh) (ModelMatrix mm _) -> enterD "Mesh changed" Linear.do
(\pipeline mesh () -> enterD "Mesh changed" Linear.do
-- For every mesh...
-- we still attach no data to the render queue, but we could, and it would be inplace of this unit
Data.traverse (\(Some @Mesh @ts mesh, ()) -> enterD "Mesh changed" Linear.do

logT "Drawing mesh"
Ur graphicsPipeline <- pure $ completelyUnsafeGraphicsPipeline pipeline
logT "Drawing mesh"
Ur graphicsPipeline <- pure $ completelyUnsafeGraphicsPipeline pipeline

-- TODO: Bind descriptor set #2

-- TODO: Bind descriptor set #2
-- TODO: No more push constants, for now!!!!
-- pLayout <- pushConstants graphicsPipeline._pipelineLayout Vk.SHADER_STAGE_VERTEX_BIT mm

-- TODO: No more push constants, for now!!!!
-- pLayout <- pushConstants graphicsPipeline._pipelineLayout Vk.SHADER_STAGE_VERTEX_BIT mm
mesh' <- renderMesh mesh
Ur _ <- pure $ Unsafe.toLinear Ur mesh'
return ()

mesh' <- renderMesh mesh
) meshes

) materials

pure (pipeline, mesh')
)
(
{-
We'll likely want to do some post-processing of user-defined
We'll likely want to do some post-processing of user-defined
render passes, but let's keep it simple and working for now. We'll
get back to a clean dear-imgui add-on to ghengin-core later.
(For each pipeline)
-}

-- Draw UI (TODO: Special render pass...?)
-- liftSystemIO IM.getDrawData >>= IM.renderDrawData
return ()
)

pure ((), cmdBuffer')
pure (consume matsunits)

) unsafeQueue
pure (consume pipesunit)

-- We can return the unsafe queue after having rendered from it because
-- rendering does not do anything to the resources in the render queue (it
-- only draws the scene specified by it) It is rather edited by the game,
-- in the loops before rendering
pure (((), CoreState{renderQueue=RenderQueue unsafeQueue, frameCounter=fcounter}), cmdBuffer')

where
-- The region of the framebuffer that the output will be rendered to. We
Expand Down Expand Up @@ -293,10 +304,10 @@ writePropertiesToResources rmap' fi
pure (rmap''', binding':##bs)


renderMesh :: MonadIO m => Mesh a RenderPassCmdM m (Mesh a)
renderMesh :: (Data.Functor m, MonadIO m) => Mesh a RenderPassCmdM m (Mesh a)
renderMesh = \case
SimpleMesh vb -> SimpleMesh <$> drawVertexBuffer vb
IndexedMesh vb ib -> uncurry IndexedMesh <$> drawVertexBufferIndexed vb ib
SimpleMesh vb -> SimpleMesh Data.<$> drawVertexBuffer vb
IndexedMesh vb ib -> uncurry IndexedMesh Data.<$> drawVertexBufferIndexed vb ib

-- completely unsafe things, todo:fix

Expand Down
3 changes: 1 addition & 2 deletions ghengin-core/ghengin-core/Ghengin/Core/Render/Pipeline.hs
Original file line number Diff line number Diff line change
Expand Up @@ -183,8 +183,7 @@ instance HasProperties (RenderPipeline π) where
pcons = RenderProperty


-- destroyRenderPipeline :: RenderPipeline α τ
-- ⊸ Renderer ()
-- destroyRenderPipeline :: RenderPipeline α τ ⊸ Renderer ()
-- destroyRenderPipeline (RenderProperty _ rp) = destroyRenderPipeline rp
-- destroyRenderPipeline (RenderPipeline gp rp dss _) = do
-- forM_ dss $ \(dset, dpool) -> do
Expand Down
Loading

0 comments on commit ec1c1b5

Please sign in to comment.