This commit is contained in:
nek0 2023-01-06 20:02:17 +01:00
parent 66455ae0d2
commit 206b331d19
7 changed files with 205 additions and 25 deletions

View file

@ -1,20 +1,26 @@
#version 450 #version 450
layout (location = 0) in vec3 vPosition; layout (location = 0) in vec3 vPosition;
layout (location = 1) in vec3 vNormal; 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 //push constants block
layout( push_constant ) uniform constants layout( push_constant ) uniform constants
{ {
vec4 data; vec4 data;
mat4 render_matrix; mat4 render_matrix;
} PushConstants; } PushConstants;
void main() 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; outColor = vColor;
} }

View file

@ -15,12 +15,16 @@ import Foreign
import Foreign.C.Types (CInt) import Foreign.C.Types (CInt)
import Linear import Linear
import qualified Vulkan as Vk import qualified Vulkan as Vk
import qualified Vulkan.CStruct.Extends as Vk
import qualified Vulkan.Zero as Vk import qualified Vulkan.Zero as Vk
import qualified VulkanMemoryAllocator as VMA
-- internal imports -- internal imports
import Devices import Devices
import Types import Types
import Memory
import Util (getFrame)
frameOverlap :: Int frameOverlap :: Int
frameOverlap = 2 frameOverlap = 2
@ -29,8 +33,11 @@ createFrames
:: (MonadResource m, MonadFail m) :: (MonadResource m, MonadFail m)
=> Vk.PhysicalDevice => Vk.PhysicalDevice
-> Vk.Device -> Vk.Device
-> VMA.Allocator
-> Vk.DescriptorPool
-> Vk.DescriptorSetLayout
-> m (V.Vector FrameData, Vk.Queue) -> m (V.Vector FrameData, Vk.Queue)
createFrames physicalDevice logicalDevice = do createFrames physicalDevice logicalDevice allocator descriptorPool setLayout = do
queueFamilyIndex <- getQueueFamily physicalDevice Vk.QUEUE_GRAPHICS_BIT queueFamilyIndex <- getQueueFamily physicalDevice Vk.QUEUE_GRAPHICS_BIT
@ -79,12 +86,43 @@ createFrames physicalDevice logicalDevice = do
Vk.destroyFence logicalDevice fence Nothing 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 return FrameData
{ framePresentSemaphore = presentSemaphore { framePresentSemaphore = presentSemaphore
, frameRenderSemaphore = renderSemaphore , frameRenderSemaphore = renderSemaphore
, frameRenderFence = renderFence , frameRenderFence = renderFence
, frameCommandPool = commandPool , frameCommandPool = commandPool
, frameMainCommandBuffer = V.head commandBuffer , frameMainCommandBuffer = V.head commandBuffer
, frameCameraBuffer = cameraBuffer
, frameGlobalDescriptor = V.head globalDescriptor
} }
) )
@ -100,6 +138,9 @@ recordCommandBuffer
-> V2 CInt -> V2 CInt
-> Vk.Pipeline -> Vk.Pipeline
-> Vk.PipelineLayout -> Vk.PipelineLayout
-> VMA.Allocator
-> FrameData
-> Int
-> m () -> m ()
recordCommandBuffer recordCommandBuffer
commandBuffer commandBuffer
@ -108,6 +149,9 @@ recordCommandBuffer
(V2 width height) (V2 width height)
graphicsPipeline graphicsPipeline
meshLayout meshLayout
allocator
frame
frameNumber
= do = do
let commandBufferBeginInfo = Vk.zero let commandBufferBeginInfo = Vk.zero
@ -166,30 +210,57 @@ recordCommandBuffer
V.mapM_ V.mapM_
(\(RenderObject meshID materialID modelMatrix) -> do (\(RenderObject meshID materialID modelMatrix) -> do
let camPosition = V3 0 0 (-5) let camPosition = V3 0 0 (-10)
camCenter = V3 0 0 0 camCenter = V3 0 0 0
camUp = V3 0 1 0 camUp = V3 0 1 0
view = lookAt camPosition camCenter camUp camView = lookAt camPosition camCenter camUp
projection = perspective (pi/4) (800 / 600) 0.1 200 camProjection = perspective (pi/4) (1280 / 1024) 0.1 200
pvm = projection !*! view !*! modelMatrix
constants = MeshPushConstants (V4 0 0 0 0) (transpose pvm) 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 mesh = meshMap M.! meshID
material = materialMap M.! materialID 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 Vk.cmdPushConstants
commandBuffer commandBuffer
meshLayout (materialPipelineLayout material)
Vk.SHADER_STAGE_VERTEX_BIT Vk.SHADER_STAGE_VERTEX_BIT
0 0
(fromIntegral $ sizeOf constants) (fromIntegral $ sizeOf constants)
pointer dataPointer
Vk.cmdBindVertexBuffers -- Vk.cmdBindVertexBuffers
commandBuffer -- commandBuffer
0 -- 0
(V.fromList [ allocatedBuffer $ meshBuffer mesh ]) -- (V.fromList [ allocatedBuffer $ meshBuffer mesh ])
(V.fromList [ 0 ]) -- (V.fromList [ 0 ])
Vk.cmdDraw commandBuffer (fromIntegral $ V.length $ meshVertices mesh) 1 0 0 Vk.cmdDraw commandBuffer (fromIntegral $ V.length $ meshVertices mesh) 1 0 0
) )

View file

@ -62,6 +62,9 @@ drawFrame engineData frameNumber = do
(engineWindowDimensions engineData) (engineWindowDimensions engineData)
(materialPipeline $ matLibrary M.! "defaultMesh") (materialPipeline $ matLibrary M.! "defaultMesh")
(meshPipelineLayout engineData) (meshPipelineLayout engineData)
(engineAllocator engineData)
frame
frameNumber
let submitInfo = Vk.zero let submitInfo = Vk.zero
{ Vk.waitSemaphores = { Vk.waitSemaphores =

View file

@ -342,8 +342,9 @@ createPipelineLayout logicalDevice = do
createMeshPipelineLayout createMeshPipelineLayout
:: MonadResource m :: MonadResource m
=> Vk.Device => Vk.Device
-> Vk.DescriptorSetLayout
-> m Vk.PipelineLayout -> m Vk.PipelineLayout
createMeshPipelineLayout logicalDevice = do createMeshPipelineLayout logicalDevice layout = do
let pushConstantRange = Vk.zero let pushConstantRange = Vk.zero
{ Vk.offset = 0 { Vk.offset = 0
, Vk.size = fromIntegral (sizeOf (undefined :: MeshPushConstants)) , Vk.size = fromIntegral (sizeOf (undefined :: MeshPushConstants))
@ -351,6 +352,7 @@ createMeshPipelineLayout logicalDevice = do
} }
pipelineLayoutCreateInfo = Vk.zero pipelineLayoutCreateInfo = Vk.zero
{ Vk.pushConstantRanges = V.singleton pushConstantRange { Vk.pushConstantRanges = V.singleton pushConstantRange
, Vk.setLayouts = V.singleton layout
} }
snd <$> allocate snd <$> allocate

View file

@ -9,6 +9,7 @@ import Control.Monad
import Control.Monad.IO.Class import Control.Monad.IO.Class
import Control.Monad.Reader import Control.Monad.Reader
import Control.Monad.Trans.Resource import Control.Monad.Trans.Resource
import Data.Bits (Bits(bit))
import qualified Data.Vector as V import qualified Data.Vector as V
import qualified SDL hiding (V2) import qualified SDL hiding (V2)
import qualified SDL.Video.Vulkan as SDL import qualified SDL.Video.Vulkan as SDL
@ -17,6 +18,8 @@ import Linear as L
import qualified Vulkan.Core10 as Vk import qualified Vulkan.Core10 as Vk
import qualified Vulkan.Extensions.VK_KHR_swapchain as Khr import qualified Vulkan.Extensions.VK_KHR_swapchain as Khr
import qualified Vulkan.Extensions.VK_KHR_surface as Khr import qualified Vulkan.Extensions.VK_KHR_surface as Khr
import qualified Vulkan.Zero as Vk
import qualified VulkanMemoryAllocator as VMA
-- internal imports -- internal imports
@ -43,6 +46,7 @@ initEngine = do
-- create a window configuration -- create a window configuration
let windowConfig = SDL.defaultWindow let windowConfig = SDL.defaultWindow
{ SDL.windowGraphicsContext = SDL.VulkanContext -- enable Vulkan support { SDL.windowGraphicsContext = SDL.VulkanContext -- enable Vulkan support
, SDL.windowInitialSize = V2 1280 1024
} }
-- load vulkan library -- load vulkan library
@ -80,6 +84,8 @@ initVulkan window = do
vulkanPhysicalDevice <- pickPhysicalDevice vulkanInstance vulkanPhysicalDevice <- pickPhysicalDevice vulkanInstance
(vulkanLogicalDevice, surfaceFormats) <- createLogicalDevice vulkanPhysicalDevice vulkanSurface (vulkanLogicalDevice, surfaceFormats) <- createLogicalDevice vulkanPhysicalDevice vulkanSurface
(descriptorSetLayout, descriptorPool) <- initDescriptors vulkanLogicalDevice
allocator <- initAllocator vulkanPhysicalDevice vulkanLogicalDevice vulkanInstance allocator <- initAllocator vulkanPhysicalDevice vulkanLogicalDevice vulkanInstance
dimensions <- liftIO $ SDL.windowInitialSize <$> SDL.getWindowConfig window dimensions <- liftIO $ SDL.windowInitialSize <$> SDL.getWindowConfig window
@ -89,7 +95,7 @@ initVulkan window = do
meshVertexShader <- loadShader vulkanLogicalDevice "shadersrc/mesh.vert" "vert" meshVertexShader <- loadShader vulkanLogicalDevice "shadersrc/mesh.vert" "vert"
meshFragmentShader <- loadShader vulkanLogicalDevice "shadersrc/rainbow.frag" "frag" meshFragmentShader <- loadShader vulkanLogicalDevice "shadersrc/rainbow.frag" "frag"
renderPass <- createRenderPass vulkanLogicalDevice (Khr.format surfaceFormat) Vk.FORMAT_D32_SFLOAT renderPass <- createRenderPass vulkanLogicalDevice (Khr.format surfaceFormat) Vk.FORMAT_D32_SFLOAT
meshLayout <- createMeshPipelineLayout vulkanLogicalDevice meshLayout <- createMeshPipelineLayout vulkanLogicalDevice descriptorSetLayout
let meshContainer = ShaderContainer (Just meshVertexShader) (Just meshFragmentShader) let meshContainer = ShaderContainer (Just meshVertexShader) (Just meshFragmentShader)
createGraphicsPipelines createGraphicsPipelines
vulkanLogicalDevice vulkanLogicalDevice
@ -101,7 +107,7 @@ initVulkan window = do
frameBuffers <- createFramebuffer vulkanLogicalDevice renderPass imageViews depthImageView dimensions frameBuffers <- createFramebuffer vulkanLogicalDevice renderPass imageViews depthImageView dimensions
(frames, queue) <- createFrames vulkanPhysicalDevice vulkanLogicalDevice (frames, queue) <- createFrames vulkanPhysicalDevice vulkanLogicalDevice allocator descriptorPool descriptorSetLayout
loadMeshes allocator loadMeshes allocator
@ -123,6 +129,8 @@ initVulkan window = do
depthAllocatedImage depthAllocatedImage
Vk.FORMAT_D32_SFLOAT Vk.FORMAT_D32_SFLOAT
frames frames
descriptorSetLayout
descriptorPool
initScene :: (MonadReader ReadState m, MonadIO m) => m () initScene :: (MonadReader ReadState m, MonadIO m) => m ()
initScene = do initScene = do
@ -154,3 +162,40 @@ initScene = do
void $ liftIO $ STM.atomically $ STM.swapTMVar renderableContainer $ void $ liftIO $ STM.atomically $ STM.swapTMVar renderableContainer $
(renderableVector `V.snoc` mask) V.++ triangles (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)

View file

@ -3,17 +3,20 @@
{-# LANGUAGE DataKinds #-} {-# LANGUAGE DataKinds #-}
module Memory where module Memory where
import Control.Monad.IO.Class (liftIO) import Control.Monad.IO.Class
import Control.Monad.Trans.Resource import Control.Monad.Trans.Resource
import Foreign.Ptr import Foreign.Ptr
import Foreign.Storable
import qualified VulkanMemoryAllocator as VMA import qualified VulkanMemoryAllocator as VMA
import qualified Vulkan.Core10 as Vk import qualified Vulkan.Core10 as Vk
import qualified Vulkan.Dynamic as Vk import qualified Vulkan.Dynamic as Vk
import qualified Vulkan.Zero as Vk import qualified Vulkan.Zero as Vk
-- internal imports
import Types
initAllocator initAllocator
:: (MonadResource m, MonadFail m) :: (MonadResource m, MonadFail m)
=> Vk.PhysicalDevice => Vk.PhysicalDevice
@ -43,3 +46,29 @@ initAllocator physicalDevice device instance' = do
) )
return allocator 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

View file

@ -39,6 +39,8 @@ data EngineData = EngineData
, engineDepthImage :: AllocatedImage , engineDepthImage :: AllocatedImage
, engineDepthFormat :: Vk.Format , engineDepthFormat :: Vk.Format
, engineFrames :: V.Vector FrameData , engineFrames :: V.Vector FrameData
, engineGlobalSetLayout :: Vk.DescriptorSetLayout
, engineDescriptorPool :: Vk.DescriptorPool
} }
data AllocatedBuffer = AllocatedBuffer data AllocatedBuffer = AllocatedBuffer
@ -184,5 +186,27 @@ data FrameData = FrameData
, frameRenderFence :: Vk.Fence , frameRenderFence :: Vk.Fence
, frameCommandPool :: Vk.CommandPool , frameCommandPool :: Vk.CommandPool
, frameMainCommandBuffer :: Vk.CommandBuffer , frameMainCommandBuffer :: Vk.CommandBuffer
, frameCameraBuffer :: AllocatedBuffer
, frameGlobalDescriptor :: Vk.DescriptorSet
} }
deriving (Show) 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