cleanup
This commit is contained in:
parent
e3bed9a2eb
commit
a2f986e852
7 changed files with 14 additions and 79 deletions
|
@ -5,6 +5,7 @@
|
|||
module CommandBuffer where
|
||||
|
||||
import qualified Control.Concurrent.STM as STM
|
||||
import Control.Exception (bracket)
|
||||
import Control.Monad
|
||||
import Control.Monad.IO.Class
|
||||
import Control.Monad.Reader
|
||||
|
@ -15,7 +16,6 @@ import Foreign hiding (void)
|
|||
import Foreign.C.Types (CInt)
|
||||
import Linear
|
||||
import qualified Vulkan as Vk
|
||||
import qualified Vulkan.CStruct.Extends as Vk
|
||||
import qualified Vulkan.Zero as Vk
|
||||
import qualified VulkanMemoryAllocator as VMA
|
||||
|
||||
|
@ -25,7 +25,6 @@ import Devices
|
|||
import Types
|
||||
import Memory
|
||||
import Util
|
||||
import Control.Exception (bracket, bracket_)
|
||||
|
||||
frameOverlap :: Int
|
||||
frameOverlap = 2
|
||||
|
@ -46,8 +45,6 @@ createFrames physicalDevice logicalDevice allocator descriptorPool setLayout obj
|
|||
|
||||
queueFamilyIndex <- getQueueFamily physicalDevice Vk.QUEUE_GRAPHICS_BIT
|
||||
|
||||
deviceProperties <- Vk.getPhysicalDeviceProperties physicalDevice
|
||||
|
||||
let poolCreateInfo = Vk.zero
|
||||
{ Vk.flags = Vk.COMMAND_POOL_CREATE_RESET_COMMAND_BUFFER_BIT
|
||||
, Vk.queueFamilyIndex = queueFamilyIndex
|
||||
|
@ -56,7 +53,7 @@ createFrames physicalDevice logicalDevice allocator descriptorPool setLayout obj
|
|||
graphicsQueue <- Vk.getDeviceQueue logicalDevice queueFamilyIndex 0
|
||||
|
||||
frames <- V.mapM
|
||||
(\index -> do
|
||||
(\_ -> do
|
||||
|
||||
commandPool <- snd <$> allocate
|
||||
(Vk.createCommandPool logicalDevice poolCreateInfo Nothing)
|
||||
|
@ -99,11 +96,6 @@ createFrames physicalDevice logicalDevice allocator descriptorPool setLayout obj
|
|||
Vk.BUFFER_USAGE_UNIFORM_BUFFER_BIT
|
||||
VMA.MEMORY_USAGE_CPU_TO_GPU
|
||||
|
||||
let sceneParamBufferSize =
|
||||
-- frameOverlap *
|
||||
fromIntegral (padUniformBufferSize
|
||||
(fromIntegral $ sizeOf undefinedGPUSceneData)
|
||||
deviceProperties)
|
||||
sceneBuffer <- createAllocatedBuffer
|
||||
allocator
|
||||
(sizeOf undefinedGPUSceneData * frameOverlap)
|
||||
|
@ -193,11 +185,8 @@ recordCommandBuffer
|
|||
-> Vk.Framebuffer
|
||||
-> V2 CInt
|
||||
-> Vk.Pipeline
|
||||
-> Vk.PipelineLayout
|
||||
-> VMA.Allocator
|
||||
-> GPUSceneData
|
||||
-> AllocatedBuffer
|
||||
-> Vk.PhysicalDeviceProperties
|
||||
-> FrameData
|
||||
-> Int
|
||||
-> m ()
|
||||
|
@ -207,11 +196,8 @@ recordCommandBuffer
|
|||
frameBuffer
|
||||
(V2 width height)
|
||||
graphicsPipeline
|
||||
meshLayout
|
||||
allocator
|
||||
sceneParameters
|
||||
sceneParameterBuffer
|
||||
deviceProps
|
||||
frame
|
||||
frameNumber
|
||||
= do
|
||||
|
@ -271,40 +257,14 @@ recordCommandBuffer
|
|||
ambientParams = sceneParameters
|
||||
{ ambientColor = ambient
|
||||
}
|
||||
frameIndex = frameNumber `mod` frameOverlap
|
||||
sceneDataOffset = padUniformBufferSize
|
||||
(fromIntegral $ sizeOf undefinedGPUSceneData)
|
||||
deviceProps
|
||||
|
||||
|
||||
liftIO $ do
|
||||
-- VMA.withMappedMemory allocator (bufferAllocation (frameSceneBuffer frame)) bracket $
|
||||
-- \scenePointer ->
|
||||
let scenePointer = VMA.mappedData (bufferInfo (frameSceneBuffer frame))
|
||||
|
||||
-- dataPointer <- liftIO $ new scenePointer
|
||||
|
||||
-- paramsPtr <- liftIO (new ambientParams)
|
||||
|
||||
-- liftIO $ copyBytes
|
||||
-- (scenePointer `plusPtr` (fromIntegral sceneDataOffset * fromIntegral frameIndex))
|
||||
-- paramsPtr
|
||||
-- (sizeOf undefinedGPUSceneData)
|
||||
|
||||
liftIO $ poke
|
||||
(castPtr scenePointer)
|
||||
-- (castPtr scenePointer `plusPtr`
|
||||
-- (fromIntegral $
|
||||
-- padUniformBufferSize (fromIntegral $ sizeOf (undefinedGPUSceneData)) deviceProps))-- *
|
||||
-- -- fromIntegral frameIndex))
|
||||
ambientParams
|
||||
|
||||
-- liftIO $ do
|
||||
-- test <- peek (castPtr scenePointer :: Ptr GPUSceneData)
|
||||
-- print test
|
||||
|
||||
-- VMA.unmapMemory allocator (bufferAllocation sceneParameterBuffer)
|
||||
|
||||
renderObjects <- (liftIO . STM.atomically . STM.readTMVar) =<< asks renderables
|
||||
meshMap <- (liftIO . STM.atomically . STM.readTMVar) =<< asks meshLibrary
|
||||
|
||||
|
@ -343,23 +303,15 @@ recordCommandBuffer
|
|||
|
||||
liftIO $ poke (castPtr memoryPointer) cameraData
|
||||
|
||||
-- VMA.unmapMemory allocator (bufferAllocation $ frameCameraBuffer frame)
|
||||
|
||||
Vk.cmdBindPipeline commandBuffer Vk.PIPELINE_BIND_POINT_GRAPHICS (materialPipeline material)
|
||||
|
||||
let uniformOffset =
|
||||
padUniformBufferSize
|
||||
(fromIntegral $ sizeOf undefinedGPUSceneData)
|
||||
deviceProps
|
||||
* fromIntegral frameIndex
|
||||
|
||||
Vk.cmdBindDescriptorSets
|
||||
commandBuffer
|
||||
Vk.PIPELINE_BIND_POINT_GRAPHICS
|
||||
(materialPipelineLayout material)
|
||||
0
|
||||
(V.singleton $ frameGlobalDescriptor frame)
|
||||
V.empty -- (V.singleton $ fromIntegral uniformOffset)
|
||||
V.empty
|
||||
|
||||
Vk.cmdBindDescriptorSets
|
||||
commandBuffer
|
||||
|
|
|
@ -61,11 +61,8 @@ drawFrame engineData frameNumber = do
|
|||
(engineFramebuffers engineData V.! fromIntegral index)
|
||||
(engineWindowDimensions engineData)
|
||||
(materialPipeline $ matLibrary M.! "defaultMesh")
|
||||
(meshPipelineLayout engineData)
|
||||
(engineAllocator engineData)
|
||||
(engineSceneParameters engineData)
|
||||
(engineSceneParameterBuffer engineData)
|
||||
(enginePhysicalDeviceProperties engineData)
|
||||
frame
|
||||
frameNumber
|
||||
|
||||
|
|
18
src/Init.hs
18
src/Init.hs
|
@ -10,14 +10,11 @@ import Control.Monad
|
|||
import Control.Monad.IO.Class
|
||||
import Control.Monad.Reader
|
||||
import Control.Monad.Trans.Resource
|
||||
import Data.Bits ((.|.))
|
||||
import qualified Data.Vector as V
|
||||
import qualified SDL hiding (V2)
|
||||
import qualified SDL.Video.Vulkan as SDL
|
||||
import Foreign (sizeOf)
|
||||
import Foreign.Ptr
|
||||
import Linear as L
|
||||
import qualified VulkanMemoryAllocator as VMA
|
||||
import qualified Vulkan.Core10 as Vk
|
||||
import qualified Vulkan.Extensions.VK_KHR_swapchain as Khr
|
||||
import qualified Vulkan.Extensions.VK_KHR_surface as Khr
|
||||
|
@ -127,7 +124,7 @@ initVulkan window = do
|
|||
|
||||
initScene
|
||||
|
||||
EngineData
|
||||
return $ EngineData
|
||||
window
|
||||
dimensions
|
||||
vulkanPhysicalDevice
|
||||
|
@ -136,7 +133,6 @@ initVulkan window = do
|
|||
swapchain
|
||||
queue
|
||||
frameBuffers
|
||||
meshLayout
|
||||
renderPass
|
||||
allocator
|
||||
depthImageView
|
||||
|
@ -146,24 +142,18 @@ initVulkan window = do
|
|||
descriptorSetLayout1
|
||||
descriptorSetLayout2
|
||||
descriptorPool
|
||||
<$> Vk.getPhysicalDeviceProperties vulkanPhysicalDevice
|
||||
<*> pure (GPUSceneData
|
||||
(GPUSceneData
|
||||
(V4 0 0 0 0)
|
||||
(V4 0 0 0 0)
|
||||
(V4 0 0 0 0)
|
||||
(V4 0 0 0 0)
|
||||
(V4 0 0 0 0)
|
||||
)
|
||||
<*> createAllocatedBuffer
|
||||
allocator
|
||||
(sizeOf undefinedGPUSceneData * frameOverlap)
|
||||
Vk.BUFFER_USAGE_UNIFORM_BUFFER_BIT
|
||||
VMA.MEMORY_USAGE_GPU_ONLY
|
||||
|
||||
|
||||
initScene :: (MonadReader ReadState m, MonadIO m) => m ()
|
||||
initScene = do
|
||||
let mask = RenderObject
|
||||
let catMask = RenderObject
|
||||
{ objectMesh = "mask"
|
||||
, objectMaterial = "defaultMesh"
|
||||
, objectMatrix = identity
|
||||
|
@ -190,7 +180,7 @@ initScene = do
|
|||
renderableVector <- liftIO $ STM.atomically $ STM.readTMVar renderableContainer
|
||||
|
||||
void $ liftIO $ STM.atomically $ STM.swapTMVar renderableContainer $
|
||||
(renderableVector `V.snoc` mask) V.++ triangles
|
||||
(renderableVector `V.snoc` catMask) V.++ triangles
|
||||
|
||||
initDescriptors
|
||||
:: (MonadResource m)
|
||||
|
|
|
@ -57,7 +57,7 @@ createAllocatedBuffer
|
|||
-> VMA.MemoryUsage
|
||||
-> m AllocatedBuffer
|
||||
createAllocatedBuffer allocator allocationSize usage memoryUsage = do
|
||||
let bufferInfo = Vk.zero
|
||||
let bufferCreateInfo = Vk.zero
|
||||
{ Vk.size = fromIntegral allocationSize
|
||||
, Vk.usage = usage
|
||||
}
|
||||
|
@ -69,7 +69,7 @@ createAllocatedBuffer allocator allocationSize usage memoryUsage = do
|
|||
} :: VMA.AllocationCreateInfo
|
||||
|
||||
(_, (buffer, newAllocation, info)) <- allocate
|
||||
(VMA.createBuffer allocator bufferInfo vmaAllocationInfo)
|
||||
(VMA.createBuffer allocator bufferCreateInfo vmaAllocationInfo)
|
||||
(\(buffer, newAllocation, _) -> do
|
||||
putStrLn "destroying buffer"
|
||||
VMA.destroyBuffer allocator buffer newAllocation
|
||||
|
|
|
@ -67,7 +67,7 @@ uploadMesh vertices allocator = do
|
|||
(buffer, bAllocation, bInfo) <- VMA.createBuffer allocator bufferCreateInfo allocationCreateInfo
|
||||
return (Mesh vertices (AllocatedBuffer buffer bAllocation bInfo))
|
||||
)
|
||||
(\(Mesh _ (AllocatedBuffer buffer bAllocation bInfo)) -> do
|
||||
(\(Mesh _ (AllocatedBuffer buffer bAllocation _)) -> do
|
||||
putStrLn "destroying mesh"
|
||||
VMA.destroyBuffer allocator buffer bAllocation
|
||||
)
|
||||
|
|
|
@ -9,7 +9,6 @@ import Control.Monad.Reader
|
|||
import Control.Monad.Trans.Resource
|
||||
import qualified Data.Map.Strict as M
|
||||
import qualified Data.Vector as V
|
||||
import Debug.Trace
|
||||
import Foreign
|
||||
import Foreign.C.Types (CInt)
|
||||
import Linear
|
||||
|
@ -33,7 +32,6 @@ data EngineData = EngineData
|
|||
, engineSwapchain :: Vk.SwapchainKHR
|
||||
, engineQueue :: Vk.Queue
|
||||
, engineFramebuffers :: V.Vector Vk.Framebuffer
|
||||
, meshPipelineLayout :: Vk.PipelineLayout
|
||||
, engineRenderPass :: Vk.RenderPass
|
||||
, engineAllocator :: VMA.Allocator
|
||||
, engineDepthImageView :: Vk.ImageView
|
||||
|
@ -43,9 +41,7 @@ data EngineData = EngineData
|
|||
, engineGlobalSetLayout :: Vk.DescriptorSetLayout
|
||||
, engineObjectSetLayout :: Vk.DescriptorSetLayout
|
||||
, engineDescriptorPool :: Vk.DescriptorPool
|
||||
, enginePhysicalDeviceProperties :: Vk.PhysicalDeviceProperties
|
||||
, engineSceneParameters :: GPUSceneData
|
||||
, engineSceneParameterBuffer :: AllocatedBuffer
|
||||
}
|
||||
|
||||
data AllocatedBuffer = AllocatedBuffer
|
||||
|
@ -138,6 +134,7 @@ data MeshPushConstants = MeshPushConstants
|
|||
}
|
||||
deriving (Show)
|
||||
|
||||
undefinedMeshPushConstants :: MeshPushConstants
|
||||
undefinedMeshPushConstants = MeshPushConstants (V4 0 0 0 0) identity
|
||||
|
||||
instance Storable MeshPushConstants where
|
||||
|
@ -210,6 +207,7 @@ newtype GPUObjectData = GPUObjectData
|
|||
{ objectModelMatrix :: M44 Float
|
||||
}
|
||||
|
||||
undefinedGPUObjectData :: GPUObjectData
|
||||
undefinedGPUObjectData = GPUObjectData identity
|
||||
|
||||
instance Storable GPUObjectData where
|
||||
|
|
|
@ -8,8 +8,6 @@ import qualified Data.Vector as V
|
|||
|
||||
import Data.Word (Word32)
|
||||
|
||||
import Debug.Trace
|
||||
|
||||
import qualified Vulkan as Vk
|
||||
import qualified Vulkan.CStruct.Extends as Vk
|
||||
import qualified Vulkan.Zero as Vk
|
||||
|
@ -58,11 +56,11 @@ writeDescriptorBuffer
|
|||
-> Vk.DescriptorBufferInfo
|
||||
-> Word32
|
||||
-> Vk.SomeStruct Vk.WriteDescriptorSet
|
||||
writeDescriptorBuffer type' dstSet bufferInfo binding = Vk.SomeStruct $
|
||||
writeDescriptorBuffer type' dstSet dBufferInfo binding = Vk.SomeStruct $
|
||||
Vk.zero
|
||||
{ Vk.dstBinding = binding
|
||||
, Vk.dstSet = dstSet
|
||||
, Vk.descriptorCount = 1
|
||||
, Vk.descriptorType = type'
|
||||
, Vk.bufferInfo = V.singleton bufferInfo
|
||||
, Vk.bufferInfo = V.singleton dBufferInfo
|
||||
}
|
||||
|
|
Loading…
Reference in a new issue