clean the states out

This commit is contained in:
nek0 2023-01-02 02:11:12 +01:00
parent f7952bf6f5
commit 5601e6fcab
3 changed files with 6 additions and 22 deletions

View file

@ -2,7 +2,6 @@
{-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE DuplicateRecordFields #-}
module Draw where module Draw where
import qualified Control.Concurrent.STM as STM
import Control.Monad import Control.Monad
import Control.Monad.Trans.Resource import Control.Monad.Trans.Resource
import qualified Data.Vector as V import qualified Data.Vector as V
@ -15,15 +14,13 @@ import qualified Vulkan.Zero as Vk
import CommandBuffer import CommandBuffer
import Types import Types
import Control.Monad.IO.Class (MonadIO(liftIO))
drawFrame drawFrame
:: (MonadResource m, MonadFail m) :: (MonadResource m, MonadFail m)
=> EngineData => EngineData
-> STM.TMVar Pipelines
-> Int -> Int
-> m () -> m ()
drawFrame engineData switch frameNumber = do drawFrame engineData frameNumber = do
unless (all (V.length (engineCommandBuffers engineData) ==) unless (all (V.length (engineCommandBuffers engineData) ==)
[ V.length (engineCommandBuffers engineData) [ V.length (engineCommandBuffers engineData)
@ -54,8 +51,6 @@ drawFrame engineData switch frameNumber = do
Vk.resetCommandBuffer Vk.resetCommandBuffer
(engineCommandBuffers engineData V.! fromIntegral index) (Vk.CommandBufferResetFlagBits 0) (engineCommandBuffers engineData V.! fromIntegral index) (Vk.CommandBufferResetFlagBits 0)
switchState <- liftIO $ STM.atomically $ STM.readTMVar switch
-- liftIO $ putStrLn "recording command buffer" -- liftIO $ putStrLn "recording command buffer"
recordCommandBuffer recordCommandBuffer
(engineCommandBuffers engineData V.! fromIntegral index) (engineCommandBuffers engineData V.! fromIntegral index)
@ -64,12 +59,7 @@ drawFrame engineData switch frameNumber = do
(engineWindowDimensions engineData) (engineWindowDimensions engineData)
(meshPipeline engineData V.! fromIntegral index) (meshPipeline engineData V.! fromIntegral index)
(meshPipelineLayout engineData) (meshPipelineLayout engineData)
(case switchState of (Just $ engineMesh engineData)
Green ->
Just $ engineMesh engineData
_ ->
Nothing
)
frameNumber frameNumber
let submitInfo = Vk.zero let submitInfo = Vk.zero

View file

@ -47,12 +47,12 @@ uploadMesh vertices allocator = do
} :: VMA.AllocationCreateInfo } :: VMA.AllocationCreateInfo
(_, mesh) <- allocate (_, mesh) <- allocate
(do (do
(buffer, allocation, _) <- VMA.createBuffer allocator bufferCreateInfo allocationCreateInfo (buffer, bAllocation, _) <- VMA.createBuffer allocator bufferCreateInfo allocationCreateInfo
return (Mesh vertices (AllocatedBuffer buffer allocation)) return (Mesh vertices (AllocatedBuffer buffer bAllocation))
) )
(\(Mesh _ (AllocatedBuffer buffer allocation)) -> do (\(Mesh _ (AllocatedBuffer buffer bAllocation)) -> do
putStrLn "destroying mesh" putStrLn "destroying mesh"
VMA.destroyBuffer allocator buffer allocation VMA.destroyBuffer allocator buffer bAllocation
) )
(dataReleaseKey, dataPtr) <- allocate (dataReleaseKey, dataPtr) <- allocate

View file

@ -10,12 +10,6 @@ import qualified Vulkan as Vk
import qualified Vulkan.Zero as Vk import qualified Vulkan.Zero as Vk
import qualified VulkanMemoryAllocator as VMA import qualified VulkanMemoryAllocator as VMA
data Pipelines
= Rainbow
| Red
| Green
deriving (Eq, Ord, Enum, Bounded)
data ShaderContainer = ShaderContainer data ShaderContainer = ShaderContainer
{ containedVertexShader :: Maybe Vk.ShaderModule { containedVertexShader :: Maybe Vk.ShaderModule
, containedFragmentShader :: Maybe Vk.ShaderModule , containedFragmentShader :: Maybe Vk.ShaderModule