wörk wörk

This commit is contained in:
nek0 2022-12-01 13:17:13 +01:00
parent b826889430
commit 6ae9fee3f0
3 changed files with 49 additions and 1 deletions

View file

@ -6,7 +6,6 @@ module Init where
import Control.Monad import Control.Monad
import Control.Monad.IO.Class import Control.Monad.IO.Class
import Control.Monad.Trans.Resource import Control.Monad.Trans.Resource
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
import Foreign.Ptr import Foreign.Ptr
@ -21,7 +20,9 @@ import Devices
import GraphicsPipeline import GraphicsPipeline
import Framebuffers import Framebuffers
import CommandBuffer import CommandBuffer
import Memory
import Types import Types
import Mesh
initEngine initEngine
:: (MonadResource m, MonadFail m) :: (MonadResource m, MonadFail m)
@ -55,6 +56,7 @@ initEngine = do
-- initialize viúlkan data structures -- initialize viúlkan data structures
initVulkan window initVulkan window
initVulkan initVulkan
:: (MonadResource m, MonadFail m) :: (MonadResource m, MonadFail m)
=> SDL.Window => SDL.Window
@ -75,6 +77,9 @@ initVulkan window = do
vulkanPhysicalDevice <- pickPhysicalDevice vulkanInstance vulkanPhysicalDevice <- pickPhysicalDevice vulkanInstance
(vulkanLogicalDevice, surfaceFormats) <- createLogicalDevice vulkanPhysicalDevice vulkanSurface (vulkanLogicalDevice, surfaceFormats) <- createLogicalDevice vulkanPhysicalDevice vulkanSurface
allocator <- initAllocator vulkanPhysicalDevice vulkanLogicalDevice vulkanInstance
mesh <- uploadMesh loadMeshes allocator
dimensions <- liftIO $ SDL.windowInitialSize <$> SDL.getWindowConfig window dimensions <- liftIO $ SDL.windowInitialSize <$> SDL.getWindowConfig window
(swapchain, surfaceFormat) <- (swapchain, surfaceFormat) <-
createSwapchain vulkanSurface surfaceFormats dimensions vulkanLogicalDevice createSwapchain vulkanSurface surfaceFormats dimensions vulkanLogicalDevice
@ -122,8 +127,10 @@ initVulkan window = do
frameBuffers frameBuffers
redPipelines redPipelines
rainbowPipelines rainbowPipelines
undefined -- placeholder for meshPipeline
renderPass renderPass
inFlightFence inFlightFence
imageAvailableSemaphore imageAvailableSemaphore
renderFinishedSemaphore renderFinishedSemaphore
mesh

View file

@ -1,10 +1,13 @@
module Types where module Types where
import qualified Data.Vector as V import qualified Data.Vector as V
import Foreign
import Foreign.Storable (Storable(..))
import Foreign.C.Types (CInt) import Foreign.C.Types (CInt)
import Linear import Linear
import qualified SDL import qualified SDL
import qualified Vulkan as Vk import qualified Vulkan as Vk
import qualified VulkanMemoryAllocator as VMA
data ShaderContainer = ShaderContainer data ShaderContainer = ShaderContainer
{ containedVertexShader :: Vk.ShaderModule { containedVertexShader :: Vk.ShaderModule
@ -22,8 +25,43 @@ data EngineData = EngineData
, engineFramebuffers :: V.Vector Vk.Framebuffer , engineFramebuffers :: V.Vector Vk.Framebuffer
, redEnginePipelines :: V.Vector Vk.Pipeline , redEnginePipelines :: V.Vector Vk.Pipeline
, rainbowEnginePipelines :: V.Vector Vk.Pipeline , rainbowEnginePipelines :: V.Vector Vk.Pipeline
, meshPipeline :: V.Vector Vk.Pipeline
, engineRenderPass :: Vk.RenderPass , engineRenderPass :: Vk.RenderPass
, engineInFlightFence :: Vk.Fence , engineInFlightFence :: Vk.Fence
, engineImageAvailableSemaphore :: Vk.Semaphore , engineImageAvailableSemaphore :: Vk.Semaphore
, engineRenderFinishedSemaphore :: Vk.Semaphore , engineRenderFinishedSemaphore :: Vk.Semaphore
, engineMesh :: Mesh
} }
data AllocatedBuffer = AllocatedBuffer
{ allocatedBuffer :: Vk.Buffer
, bufferAllocation :: VMA.Allocation
}
deriving (Show)
data Vertex = Vertex
{ vertexPosition :: V3 Float
, vertexNormal :: V3 Float
, vertexColor :: V4 Float
}
deriving (Show)
instance Storable Vertex where
sizeOf (Vertex position normal color) = sizeOf position + sizeOf normal + sizeOf color
peek _ = undefined
poke ptr (Vertex position normal color) = do
let castedV3Ptr = castPtr ptr
pokeElemOff castedV3Ptr 0 position
pokeElemOff castedV3Ptr 1 normal
poke (castPtr (ptr `plusPtr` sizeOf position `plusPtr` sizeOf normal)) color
alignment _ = undefined
data Mesh = Mesh
{ meshVertices :: V.Vector Vertex
, meshBuffer :: AllocatedBuffer
}
deriving (Show)

View file

@ -31,6 +31,8 @@ executable vulkan-tutorial
Framebuffers Framebuffers
CommandBuffer CommandBuffer
Draw Draw
Memory
Mesh
Types Types
-- LANGUAGE extensions used by modules in this package. -- LANGUAGE extensions used by modules in this package.
@ -39,6 +41,7 @@ executable vulkan-tutorial
, sdl2 , sdl2
, vulkan , vulkan
, vulkan-utils , vulkan-utils
, VulkanMemoryAllocator
, linear , linear
, monad-loops , monad-loops
, stm , stm