From 206b331d19712005c6f2faa08f673dd4f10467ae Mon Sep 17 00:00:00 2001 From: nek0 Date: Fri, 6 Jan 2023 20:02:17 +0100 Subject: [PATCH] blah --- shadersrc/mesh.vert | 18 +++++--- src/CommandBuffer.hs | 99 +++++++++++++++++++++++++++++++++++------ src/Draw.hs | 3 ++ src/GraphicsPipeline.hs | 4 +- src/Init.hs | 49 +++++++++++++++++++- src/Memory.hs | 33 +++++++++++++- src/Types.hs | 24 ++++++++++ 7 files changed, 205 insertions(+), 25 deletions(-) diff --git a/shadersrc/mesh.vert b/shadersrc/mesh.vert index 293b3bd..448df68 100644 --- a/shadersrc/mesh.vert +++ b/shadersrc/mesh.vert @@ -1,20 +1,26 @@ #version 450 - layout (location = 0) in vec3 vPosition; layout (location = 1) in vec3 vNormal; -layout (location = 2) in vec4 vColor; +layout (location = 2) in vec3 vColor; -layout (location = 0) out vec4 outColor; +layout (location = 0) out vec3 outColor; + +layout(set = 0, binding = 0) uniform CameraBuffer{ + mat4 view; + mat4 proj; + mat4 viewproj; +} cameraData; //push constants block layout( push_constant ) uniform constants { - vec4 data; - mat4 render_matrix; + vec4 data; + mat4 render_matrix; } PushConstants; void main() { - gl_Position = PushConstants.render_matrix * vec4(vPosition, 1.0f); + mat4 transformMatrix = (cameraData.viewproj * PushConstants.render_matrix); + gl_Position = transformMatrix * vec4(vPosition, 1.0f); outColor = vColor; } diff --git a/src/CommandBuffer.hs b/src/CommandBuffer.hs index ae1268b..7581c22 100644 --- a/src/CommandBuffer.hs +++ b/src/CommandBuffer.hs @@ -15,12 +15,16 @@ import Foreign 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 -- internal imports import Devices import Types +import Memory +import Util (getFrame) frameOverlap :: Int frameOverlap = 2 @@ -29,8 +33,11 @@ createFrames :: (MonadResource m, MonadFail m) => Vk.PhysicalDevice -> Vk.Device + -> VMA.Allocator + -> Vk.DescriptorPool + -> Vk.DescriptorSetLayout -> m (V.Vector FrameData, Vk.Queue) -createFrames physicalDevice logicalDevice = do +createFrames physicalDevice logicalDevice allocator descriptorPool setLayout = do queueFamilyIndex <- getQueueFamily physicalDevice Vk.QUEUE_GRAPHICS_BIT @@ -79,12 +86,43 @@ createFrames physicalDevice logicalDevice = do Vk.destroyFence logicalDevice fence Nothing ) + cameraBuffer <- createAllocatedBuffer + logicalDevice + allocator + (sizeOf (GPUCameraData identity identity identity)) + Vk.BUFFER_USAGE_UNIFORM_BUFFER_BIT + VMA.MEMORY_USAGE_CPU_TO_GPU + + + let allocationInfo = Vk.zero + { Vk.descriptorPool = descriptorPool + , Vk.setLayouts = V.singleton setLayout + } + + globalDescriptor <- Vk.allocateDescriptorSets logicalDevice allocationInfo + + let bufferInfo = Vk.zero + { Vk.buffer = allocatedBuffer cameraBuffer + , Vk.offset = 0 + , Vk.range = fromIntegral $ sizeOf (GPUCameraData identity identity identity) + } :: Vk.DescriptorBufferInfo + setWrite = Vk.zero + { Vk.dstBinding = 0 + , Vk.dstSet = V.head globalDescriptor + , Vk.descriptorType = Vk.DESCRIPTOR_TYPE_UNIFORM_BUFFER + , Vk.bufferInfo = V.singleton bufferInfo + } + + Vk.updateDescriptorSets logicalDevice (V.singleton (Vk.SomeStruct setWrite)) V.empty + return FrameData { framePresentSemaphore = presentSemaphore , frameRenderSemaphore = renderSemaphore , frameRenderFence = renderFence , frameCommandPool = commandPool , frameMainCommandBuffer = V.head commandBuffer + , frameCameraBuffer = cameraBuffer + , frameGlobalDescriptor = V.head globalDescriptor } ) @@ -100,6 +138,9 @@ recordCommandBuffer -> V2 CInt -> Vk.Pipeline -> Vk.PipelineLayout + -> VMA.Allocator + -> FrameData + -> Int -> m () recordCommandBuffer commandBuffer @@ -108,6 +149,9 @@ recordCommandBuffer (V2 width height) graphicsPipeline meshLayout + allocator + frame + frameNumber = do let commandBufferBeginInfo = Vk.zero @@ -166,30 +210,57 @@ recordCommandBuffer V.mapM_ (\(RenderObject meshID materialID modelMatrix) -> do - let camPosition = V3 0 0 (-5) + let camPosition = V3 0 0 (-10) camCenter = V3 0 0 0 camUp = V3 0 1 0 - view = lookAt camPosition camCenter camUp - projection = perspective (pi/4) (800 / 600) 0.1 200 - pvm = projection !*! view !*! modelMatrix - constants = MeshPushConstants (V4 0 0 0 0) (transpose pvm) + camView = lookAt camPosition camCenter camUp + camProjection = perspective (pi/4) (1280 / 1024) 0.1 200 + + cameraData = GPUCameraData + { view = camView + , projection = camProjection + , viewProjection = camProjection !*! camView + } + + -- pvm = projection !*! view !*! modelMatrix + constants = MeshPushConstants + { meshPushData = V4 0 0 0 0 + , meshRenderMatrix = transpose modelMatrix + } mesh = meshMap M.! meshID material = materialMap M.! materialID - pointer <- liftIO (castPtr <$> new constants) + memoryPointer <- VMA.mapMemory allocator (bufferAllocation $ frameCameraBuffer frame) + + liftIO $ poke (castPtr memoryPointer) cameraData + + VMA.unmapMemory allocator (bufferAllocation $ frameCameraBuffer frame) + + Vk.cmdBindPipeline commandBuffer Vk.PIPELINE_BIND_POINT_GRAPHICS (materialPipeline material) + + Vk.cmdBindDescriptorSets + commandBuffer + Vk.PIPELINE_BIND_POINT_GRAPHICS + (materialPipelineLayout material) + 0 + (V.singleton $ frameGlobalDescriptor frame) + V.empty + + dataPointer <- liftIO (castPtr <$> new constants) + Vk.cmdPushConstants commandBuffer - meshLayout + (materialPipelineLayout material) Vk.SHADER_STAGE_VERTEX_BIT 0 (fromIntegral $ sizeOf constants) - pointer + dataPointer - Vk.cmdBindVertexBuffers - commandBuffer - 0 - (V.fromList [ allocatedBuffer $ meshBuffer mesh ]) - (V.fromList [ 0 ]) + -- Vk.cmdBindVertexBuffers + -- commandBuffer + -- 0 + -- (V.fromList [ allocatedBuffer $ meshBuffer mesh ]) + -- (V.fromList [ 0 ]) Vk.cmdDraw commandBuffer (fromIntegral $ V.length $ meshVertices mesh) 1 0 0 ) diff --git a/src/Draw.hs b/src/Draw.hs index 55fd27f..e3de7f8 100644 --- a/src/Draw.hs +++ b/src/Draw.hs @@ -62,6 +62,9 @@ drawFrame engineData frameNumber = do (engineWindowDimensions engineData) (materialPipeline $ matLibrary M.! "defaultMesh") (meshPipelineLayout engineData) + (engineAllocator engineData) + frame + frameNumber let submitInfo = Vk.zero { Vk.waitSemaphores = diff --git a/src/GraphicsPipeline.hs b/src/GraphicsPipeline.hs index ac7dcb3..7ca6cc8 100644 --- a/src/GraphicsPipeline.hs +++ b/src/GraphicsPipeline.hs @@ -342,8 +342,9 @@ createPipelineLayout logicalDevice = do createMeshPipelineLayout :: MonadResource m => Vk.Device + -> Vk.DescriptorSetLayout -> m Vk.PipelineLayout -createMeshPipelineLayout logicalDevice = do +createMeshPipelineLayout logicalDevice layout = do let pushConstantRange = Vk.zero { Vk.offset = 0 , Vk.size = fromIntegral (sizeOf (undefined :: MeshPushConstants)) @@ -351,6 +352,7 @@ createMeshPipelineLayout logicalDevice = do } pipelineLayoutCreateInfo = Vk.zero { Vk.pushConstantRanges = V.singleton pushConstantRange + , Vk.setLayouts = V.singleton layout } snd <$> allocate diff --git a/src/Init.hs b/src/Init.hs index e8d6c44..de6c991 100644 --- a/src/Init.hs +++ b/src/Init.hs @@ -9,6 +9,7 @@ import Control.Monad import Control.Monad.IO.Class import Control.Monad.Reader import Control.Monad.Trans.Resource +import Data.Bits (Bits(bit)) import qualified Data.Vector as V import qualified SDL hiding (V2) import qualified SDL.Video.Vulkan as SDL @@ -17,6 +18,8 @@ import Linear as L import qualified Vulkan.Core10 as Vk import qualified Vulkan.Extensions.VK_KHR_swapchain as Khr import qualified Vulkan.Extensions.VK_KHR_surface as Khr +import qualified Vulkan.Zero as Vk +import qualified VulkanMemoryAllocator as VMA -- internal imports @@ -43,6 +46,7 @@ initEngine = do -- create a window configuration let windowConfig = SDL.defaultWindow { SDL.windowGraphicsContext = SDL.VulkanContext -- enable Vulkan support + , SDL.windowInitialSize = V2 1280 1024 } -- load vulkan library @@ -80,6 +84,8 @@ initVulkan window = do vulkanPhysicalDevice <- pickPhysicalDevice vulkanInstance (vulkanLogicalDevice, surfaceFormats) <- createLogicalDevice vulkanPhysicalDevice vulkanSurface + (descriptorSetLayout, descriptorPool) <- initDescriptors vulkanLogicalDevice + allocator <- initAllocator vulkanPhysicalDevice vulkanLogicalDevice vulkanInstance dimensions <- liftIO $ SDL.windowInitialSize <$> SDL.getWindowConfig window @@ -89,7 +95,7 @@ initVulkan window = do meshVertexShader <- loadShader vulkanLogicalDevice "shadersrc/mesh.vert" "vert" meshFragmentShader <- loadShader vulkanLogicalDevice "shadersrc/rainbow.frag" "frag" renderPass <- createRenderPass vulkanLogicalDevice (Khr.format surfaceFormat) Vk.FORMAT_D32_SFLOAT - meshLayout <- createMeshPipelineLayout vulkanLogicalDevice + meshLayout <- createMeshPipelineLayout vulkanLogicalDevice descriptorSetLayout let meshContainer = ShaderContainer (Just meshVertexShader) (Just meshFragmentShader) createGraphicsPipelines vulkanLogicalDevice @@ -101,7 +107,7 @@ initVulkan window = do frameBuffers <- createFramebuffer vulkanLogicalDevice renderPass imageViews depthImageView dimensions - (frames, queue) <- createFrames vulkanPhysicalDevice vulkanLogicalDevice + (frames, queue) <- createFrames vulkanPhysicalDevice vulkanLogicalDevice allocator descriptorPool descriptorSetLayout loadMeshes allocator @@ -123,6 +129,8 @@ initVulkan window = do depthAllocatedImage Vk.FORMAT_D32_SFLOAT frames + descriptorSetLayout + descriptorPool initScene :: (MonadReader ReadState m, MonadIO m) => m () initScene = do @@ -154,3 +162,40 @@ initScene = do void $ liftIO $ STM.atomically $ STM.swapTMVar renderableContainer $ (renderableVector `V.snoc` mask) V.++ triangles + +initDescriptors + :: (MonadResource m) + => Vk.Device + -> m (Vk.DescriptorSetLayout, Vk.DescriptorPool) +initDescriptors device = do + let cameraBufferBinding = Vk.zero + { Vk.binding = 0 + , Vk.descriptorCount = 1 + , Vk.descriptorType = Vk.DESCRIPTOR_TYPE_UNIFORM_BUFFER + , Vk.stageFlags = Vk.SHADER_STAGE_VERTEX_BIT + } + setInfo = Vk.zero + { Vk.flags = bit 0 + , Vk.bindings = V.singleton cameraBufferBinding + } + poolInfo = Vk.zero + { Vk.flags = bit 0 + , Vk.maxSets = 10 + , Vk.poolSizes = V.singleton (Vk.DescriptorPoolSize Vk.DESCRIPTOR_TYPE_UNIFORM_BUFFER 10) + } + + (_, descriptorSetLayout) <- allocate + (Vk.createDescriptorSetLayout device setInfo Nothing) + (\descriptorLayout -> do + putStrLn "destroying descriptor layout" + Vk.destroyDescriptorSetLayout device descriptorLayout Nothing + ) + + (_, descriptorPool) <- allocate + (Vk.createDescriptorPool device poolInfo Nothing) + (\descriptorPoolInfo -> do + putStrLn "destroying descriptor pool" + Vk.destroyDescriptorPool device descriptorPoolInfo Nothing + ) + + return (descriptorSetLayout, descriptorPool) diff --git a/src/Memory.hs b/src/Memory.hs index 0eb74f4..5eff86c 100644 --- a/src/Memory.hs +++ b/src/Memory.hs @@ -3,17 +3,20 @@ {-# LANGUAGE DataKinds #-} module Memory where -import Control.Monad.IO.Class (liftIO) +import Control.Monad.IO.Class import Control.Monad.Trans.Resource import Foreign.Ptr -import Foreign.Storable import qualified VulkanMemoryAllocator as VMA import qualified Vulkan.Core10 as Vk import qualified Vulkan.Dynamic as Vk import qualified Vulkan.Zero as Vk +-- internal imports + +import Types + initAllocator :: (MonadResource m, MonadFail m) => Vk.PhysicalDevice @@ -43,3 +46,29 @@ initAllocator physicalDevice device instance' = do ) return allocator + +createAllocatedBuffer + :: (MonadResource m, MonadIO m) + => Vk.Device + -> VMA.Allocator + -> Int + -> Vk.BufferUsageFlags + -> VMA.MemoryUsage + -> m AllocatedBuffer +createAllocatedBuffer device allocator allocationSize usage memoryUsage = do + let bufferInfo = Vk.zero + { Vk.size = fromIntegral allocationSize + , Vk.usage = usage + } + vmaAllocationInfo = Vk.zero + { VMA.usage = memoryUsage + } :: VMA.AllocationCreateInfo + + (_, (buffer, newAllocation, _)) <- allocate + (VMA.createBuffer allocator bufferInfo vmaAllocationInfo) + (\(buffer, _, _) -> do + putStrLn "destroying buffer" + Vk.destroyBuffer device buffer Nothing + ) + + return $ AllocatedBuffer buffer newAllocation diff --git a/src/Types.hs b/src/Types.hs index c780c88..f7d7845 100644 --- a/src/Types.hs +++ b/src/Types.hs @@ -39,6 +39,8 @@ data EngineData = EngineData , engineDepthImage :: AllocatedImage , engineDepthFormat :: Vk.Format , engineFrames :: V.Vector FrameData + , engineGlobalSetLayout :: Vk.DescriptorSetLayout + , engineDescriptorPool :: Vk.DescriptorPool } data AllocatedBuffer = AllocatedBuffer @@ -184,5 +186,27 @@ data FrameData = FrameData , frameRenderFence :: Vk.Fence , frameCommandPool :: Vk.CommandPool , frameMainCommandBuffer :: Vk.CommandBuffer + , frameCameraBuffer :: AllocatedBuffer + , frameGlobalDescriptor :: Vk.DescriptorSet } deriving (Show) + +data GPUCameraData = GPUCameraData + { view :: M44 Float + , projection :: M44 Float + , viewProjection :: M44 Float + } + +instance Storable GPUCameraData where + + sizeOf (GPUCameraData view projection viewProjection) = + sizeOf view + sizeOf projection + sizeOf viewProjection + + alignment = undefined + + peek _ = undefined + + poke ptr (GPUCameraData view projection viewProjection) = do + poke (castPtr ptr) view + poke (castPtr ptr `plusPtr` sizeOf view) projection + poke (castPtr ptr `plusPtr` sizeOf view `plusPtr` sizeOf projection) viewProjection