draw textured object

This commit is contained in:
nek0 2023-05-16 11:14:46 +02:00
parent 32bc3fc4b4
commit e91afc8ada
14 changed files with 3443 additions and 46 deletions

13
assets/models/jaeger.mtl Executable file
View file

@ -0,0 +1,13 @@
# Blender MTL File: 'jaeger.blend'
# Material Count: 1
newmtl Material_jaeger.texture.tga
Ns 92.156863
Ka 1.000000 1.000000 1.000000
Kd 0.512000 0.512000 0.512000
Ks 0.500000 0.500000 0.500000
Ke 0.000000 0.000000 0.000000
Ni 1.000000
d 1.000000
illum 2
map_Kd jaeger.texture.tga

1237
assets/models/jaeger.obj Executable file

File diff suppressed because it is too large Load diff

1960
assets/models/marksman.obj Executable file

File diff suppressed because it is too large Load diff

Binary file not shown.

After

Width:  |  Height:  |  Size: 4 MiB

Binary file not shown.

After

Width:  |  Height:  |  Size: 4 MiB

View file

@ -0,0 +1,24 @@
//glsl version 4.5
#version 450
//shader input
layout (location = 0) in vec4 inColor;
layout (location = 1) in vec2 texCoord;
//output write
layout (location = 0) out vec4 outFragColor;
layout(set = 0, binding = 1) uniform SceneData{
vec4 fogColor; // w is for exponent
vec4 fogDistances; //x for min, y for max, zw unused.
vec4 ambientColor;
vec4 sunlightDirection; //w for sun power
vec4 sunlightColor;
} sceneData;
layout(set = 2, binding = 0) uniform sampler2D tex1;
void main()
{
vec3 color = texture(tex1,texCoord).xyz;
outFragColor = vec4(color, inColor.w);
}

View file

@ -2,8 +2,10 @@
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 vec4 vColor;
layout (location = 3) in vec2 vTexCoord;
layout (location = 0) out vec4 outColor; layout (location = 0) out vec4 outColor;
layout (location = 1) out vec2 texCoord;
layout(set = 0, binding = 0) uniform CameraBuffer{ layout(set = 0, binding = 0) uniform CameraBuffer{
mat4 view; mat4 view;
@ -34,4 +36,5 @@ void main()
mat4 transformMatrix = (cameraData.viewproj * modelMatrix); mat4 transformMatrix = (cameraData.viewproj * modelMatrix);
gl_Position = transformMatrix * vec4(vPosition, 1.0f); gl_Position = transformMatrix * vec4(vPosition, 1.0f);
outColor = vColor; outColor = vColor;
texCoord = vTexCoord;
} }

View file

@ -23,6 +23,7 @@ import qualified VulkanMemoryAllocator as VMA
import Types import Types
import Memory import Memory
import Util import Util
import Data.Maybe (fromMaybe)
frameOverlap :: Int frameOverlap :: Int
frameOverlap = 2 frameOverlap = 2
@ -230,8 +231,23 @@ recordCommandBuffer
{ meshPushData = V4 0 0 0 0 { meshPushData = V4 0 0 0 0
, meshRenderMatrix = modelMatrix , meshRenderMatrix = modelMatrix
} }
mesh = meshMap M.! meshID mesh = fromMaybe
material = materialMap M.! materialID (error $ "no mesh called " <> meshID <> " present")
(meshMap M.!? meshID)
material = fromMaybe
(error $ "no material called " <> materialID <> " present")
(materialMap M.!? materialID)
when
(materialTextureSet material /= Vk.NULL_HANDLE)
(Vk.cmdBindDescriptorSets
commandBuffer
Vk.PIPELINE_BIND_POINT_GRAPHICS
(materialPipelineLayout material)
2
(V.singleton $ materialTextureSet material)
V.empty
)
Vk.cmdBindPipeline commandBuffer Vk.PIPELINE_BIND_POINT_GRAPHICS (materialPipeline material) Vk.cmdBindPipeline commandBuffer Vk.PIPELINE_BIND_POINT_GRAPHICS (materialPipeline material)

View file

@ -194,6 +194,7 @@ createGraphicsPipelines
-> V2 CInt -> V2 CInt
-> Vk.PipelineLayout -> Vk.PipelineLayout
-> Maybe Vk.PipelineDepthStencilStateCreateInfo -> Maybe Vk.PipelineDepthStencilStateCreateInfo
-> String
-> m () -> m ()
createGraphicsPipelines createGraphicsPipelines
logicalDevice logicalDevice
@ -202,6 +203,7 @@ createGraphicsPipelines
(V2 width height) (V2 width height)
pipelineLayout pipelineLayout
depthState depthState
materialName
= do = do
meshLib <- (liftIO . STM.atomically . STM.readTMVar) =<< asks meshLibrary meshLib <- (liftIO . STM.atomically . STM.readTMVar) =<< asks meshLibrary
let pipelineStagesCreateInfos = let pipelineStagesCreateInfos =
@ -304,10 +306,10 @@ createGraphicsPipelines
error "createGraphicsPipelines: Failed creating pipelines" error "createGraphicsPipelines: Failed creating pipelines"
return pipelines return pipelines
) )
let material = Material (V.head pipeline) pipelineLayout let material = Material Vk.NULL_HANDLE (V.head pipeline) pipelineLayout
matLibraryTMVar <- asks materialLibrary matLibraryTMVar <- asks materialLibrary
matLibrary <- liftIO $ STM.atomically $ STM.readTMVar matLibraryTMVar matLibrary <- liftIO $ STM.atomically $ STM.readTMVar matLibraryTMVar
let newMatLibrary = M.insert "defaultMesh" material matLibrary let newMatLibrary = M.insert materialName material matLibrary
void $ liftIO $ STM.atomically $ STM.swapTMVar matLibraryTMVar newMatLibrary void $ liftIO $ STM.atomically $ STM.swapTMVar matLibraryTMVar newMatLibrary
createMeshPipelineLayout createMeshPipelineLayout

View file

@ -10,12 +10,15 @@ 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 qualified Data.Map.Strict as M
import Data.Maybe
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
import Foreign.Ptr import Foreign.Ptr
import Linear as L import Linear as L
import qualified Vulkan.Core10 as Vk import qualified Vulkan as Vk
import qualified Vulkan.CStruct.Extends 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 Vulkan.Zero as Vk
@ -94,7 +97,8 @@ initVulkan window = do
uploadContext <- initSyncStructures vulkanLogicalDevice queueIndex uploadContext <- initSyncStructures vulkanLogicalDevice queueIndex
(descriptorSetLayout1, descriptorSetLayout2, descriptorPool) <- initDescriptors vulkanLogicalDevice (descriptorSetLayout1, descriptorSetLayout2, textureDescriptorSetLayout, descriptorPool) <-
initDescriptors vulkanLogicalDevice
allocator <- initAllocator vulkanPhysicalDevice vulkanLogicalDevice vulkanInstance allocator <- initAllocator vulkanPhysicalDevice vulkanLogicalDevice vulkanInstance
@ -104,15 +108,26 @@ initVulkan window = do
imageViews <- getImageViewHandles swapchain surfaceFormat vulkanLogicalDevice imageViews <- getImageViewHandles swapchain surfaceFormat vulkanLogicalDevice
meshVertexShader <- loadShader vulkanLogicalDevice "shadersrc/tri_mesh.vert" "vert" meshVertexShader <- loadShader vulkanLogicalDevice "shadersrc/tri_mesh.vert" "vert"
meshFragmentShader <- loadShader vulkanLogicalDevice "shadersrc/rainbow_lit.frag" "frag" meshFragmentShader <- loadShader vulkanLogicalDevice "shadersrc/rainbow_lit.frag" "frag"
textureFragmentShader <- loadShader vulkanLogicalDevice "shadersrc/textured_lit.frag" "frag"
renderPass <- createRenderPass vulkanLogicalDevice (Khr.format surfaceFormat) Vk.FORMAT_D32_SFLOAT renderPass <- createRenderPass vulkanLogicalDevice (Khr.format surfaceFormat) Vk.FORMAT_D32_SFLOAT
meshLayout <- createMeshPipelineLayout meshLayout <- createMeshPipelineLayout
vulkanLogicalDevice vulkanLogicalDevice
(V.fromList (V.fromList
[ descriptorSetLayout1 [ descriptorSetLayout1
, descriptorSetLayout2 , descriptorSetLayout2
, textureDescriptorSetLayout
]
)
textureLayout <- createMeshPipelineLayout
vulkanLogicalDevice
(V.fromList
[ descriptorSetLayout1
, descriptorSetLayout2
, textureDescriptorSetLayout
] ]
) )
let meshContainer = ShaderContainer (Just meshVertexShader) (Just meshFragmentShader) let meshContainer = ShaderContainer (Just meshVertexShader) (Just meshFragmentShader)
textureContainer = ShaderContainer (Just meshVertexShader) (Just textureFragmentShader)
createGraphicsPipelines createGraphicsPipelines
vulkanLogicalDevice vulkanLogicalDevice
renderPass renderPass
@ -120,6 +135,15 @@ initVulkan window = do
dimensions dimensions
meshLayout meshLayout
(Just (createDepthStencilStateCreateInfo True True Vk.COMPARE_OP_LESS_OR_EQUAL)) (Just (createDepthStencilStateCreateInfo True True Vk.COMPARE_OP_LESS_OR_EQUAL))
"defaultMesh"
createGraphicsPipelines
vulkanLogicalDevice
renderPass
textureContainer
dimensions
textureLayout
(Just (createDepthStencilStateCreateInfo True True Vk.COMPARE_OP_LESS_OR_EQUAL))
"texturedMesh"
frameBuffers <- createFramebuffer vulkanLogicalDevice renderPass imageViews depthImageView dimensions frameBuffers <- createFramebuffer vulkanLogicalDevice renderPass imageViews depthImageView dimensions
@ -136,7 +160,7 @@ initVulkan window = do
loadImages allocator uploadContext queue vulkanLogicalDevice loadImages allocator uploadContext queue vulkanLogicalDevice
initScene initScene vulkanLogicalDevice descriptorPool textureDescriptorSetLayout
return $ EngineData return $ EngineData
window window
@ -155,6 +179,7 @@ initVulkan window = do
frames frames
descriptorSetLayout1 descriptorSetLayout1
descriptorSetLayout2 descriptorSetLayout2
textureDescriptorSetLayout
descriptorPool descriptorPool
(GPUSceneData (GPUSceneData
(V4 0 0 0 0) (V4 0 0 0 0)
@ -166,11 +191,16 @@ initVulkan window = do
uploadContext uploadContext
initScene :: (MonadReader ReadState m, MonadIO m) => m () initScene
initScene = do :: (MonadReader ReadState m, MonadIO m, MonadResource m)
=> Vk.Device
-> Vk.DescriptorPool
-> Vk.DescriptorSetLayout
-> m ()
initScene device descriptorPool texturedSetLayout = do
let catMask = RenderObject let catMask = RenderObject
{ objectMesh = "mask" { objectMesh = "mask"
, objectMaterial = "defaultMesh" , objectMaterial = "texturedMesh"
, objectMatrix = identity , objectMatrix = identity
} }
triangles = V.concatMap triangles = V.concatMap
@ -197,10 +227,51 @@ initScene = do
void $ liftIO $ STM.atomically $ STM.swapTMVar renderableContainer $ void $ liftIO $ STM.atomically $ STM.swapTMVar renderableContainer $
(renderableVector `V.snoc` catMask) V.++ triangles (renderableVector `V.snoc` catMask) V.++ triangles
let samplerInfo = samplerCreateInfo Vk.FILTER_NEAREST Vk.SAMPLER_ADDRESS_MODE_REPEAT
blockySampler <- snd <$> Vk.withSampler device samplerInfo Nothing allocate
matLibraryContainer <- asks materialLibrary
texturedMaterial <- do
matLibrary <- liftIO $ STM.atomically $ STM.readTMVar matLibraryContainer
return (fromMaybe (error "not texturedMesh") $ matLibrary M.!? "texturedMesh")
let allocInfo = Vk.zero
{ Vk.descriptorPool = descriptorPool
, Vk.setLayouts = V.singleton texturedSetLayout
}
texturedDescriptorSet <- V.head . snd <$> Vk.withDescriptorSets device allocInfo allocate
liftIO $ do
matLibrary <- STM.atomically $ STM.readTMVar matLibraryContainer
let material = texturedMaterial
{ materialTextureSet = texturedDescriptorSet
}
newMatLibrary = M.insert "texturedMesh" material matLibrary
void $ STM.atomically $ STM.swapTMVar matLibraryContainer newMatLibrary
textureContainer <- asks textureLibrary
texture <- do
texLibrary <- liftIO $ STM.atomically $ STM.readTMVar textureContainer
return $ fromMaybe (error "no marksman texture found") $ texLibrary M.!? "marksman"
let imageBufferInfo = Vk.zero
{ Vk.sampler = blockySampler
, Vk.imageView = textureImageView texture
, Vk.imageLayout = Vk.IMAGE_LAYOUT_SHADER_READ_ONLY_OPTIMAL
}
texture1 = V.singleton $ Vk.SomeStruct $ writeDescriptorImage
Vk.DESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER
texturedDescriptorSet
imageBufferInfo
0
Vk.updateDescriptorSets device texture1 V.empty
initDescriptors initDescriptors
:: (MonadResource m) :: (MonadResource m)
=> Vk.Device => Vk.Device
-> m (Vk.DescriptorSetLayout, Vk.DescriptorSetLayout, Vk.DescriptorPool) -> m (Vk.DescriptorSetLayout, Vk.DescriptorSetLayout, Vk.DescriptorSetLayout, Vk.DescriptorPool)
initDescriptors device = do initDescriptors device = do
let cameraBind = descriptorsetLayoutBinding let cameraBind = descriptorsetLayoutBinding
Vk.DESCRIPTOR_TYPE_UNIFORM_BUFFER Vk.DESCRIPTOR_TYPE_UNIFORM_BUFFER
@ -214,6 +285,10 @@ initDescriptors device = do
Vk.DESCRIPTOR_TYPE_STORAGE_BUFFER Vk.DESCRIPTOR_TYPE_STORAGE_BUFFER
Vk.SHADER_STAGE_VERTEX_BIT Vk.SHADER_STAGE_VERTEX_BIT
0 0
textureBind = descriptorsetLayoutBinding
Vk.DESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER
Vk.SHADER_STAGE_FRAGMENT_BIT
0
setInfo = Vk.zero setInfo = Vk.zero
{ Vk.flags = Vk.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT { Vk.flags = Vk.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT
, Vk.bindings = V.fromList , Vk.bindings = V.fromList
@ -225,6 +300,10 @@ initDescriptors device = do
{ Vk.flags = Vk.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT { Vk.flags = Vk.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT
, Vk.bindings = V.singleton objectBind , Vk.bindings = V.singleton objectBind
} }
setInfo3 = Vk.zero
{ Vk.flags = Vk.DESCRIPTOR_SET_LAYOUT_CREATE_UPDATE_AFTER_BIND_POOL_BIT
, Vk.bindings = V.singleton textureBind
}
poolInfo = Vk.zero poolInfo = Vk.zero
{ Vk.flags = Vk.DESCRIPTOR_POOL_CREATE_UPDATE_AFTER_BIND_BIT { Vk.flags = Vk.DESCRIPTOR_POOL_CREATE_UPDATE_AFTER_BIND_BIT
, Vk.maxSets = 10 , Vk.maxSets = 10
@ -241,6 +320,10 @@ initDescriptors device = do
{ Vk.type' = Vk.DESCRIPTOR_TYPE_STORAGE_BUFFER { Vk.type' = Vk.DESCRIPTOR_TYPE_STORAGE_BUFFER
, Vk.descriptorCount = 10 , Vk.descriptorCount = 10
} }
, Vk.zero
{ Vk.type' = Vk.DESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER
, Vk.descriptorCount = 10
}
] ]
} }
@ -253,4 +336,7 @@ initDescriptors device = do
(_, descriptorPool) <- (_, descriptorPool) <-
Vk.withDescriptorPool device poolInfo Nothing allocate Vk.withDescriptorPool device poolInfo Nothing allocate
return (descriptorSetLayout1, descriptorSetLayout2, descriptorPool) (_, textureDescriptorSetLayout) <-
Vk.withDescriptorSetLayout device setInfo3 Nothing allocate
return (descriptorSetLayout1, descriptorSetLayout2, textureDescriptorSetLayout, descriptorPool)

View file

@ -13,11 +13,14 @@ import Control.Monad.Reader
import Control.Monad.Trans.Resource import Control.Monad.Trans.Resource
import qualified Data.Map.Strict as M import qualified Data.Map.Strict as M
import Data.Maybe (fromMaybe)
import qualified Data.Vector as V import qualified Data.Vector as V
import Debug.Trace
import Foreign import Foreign
import Linear (V3(..), V4(..)) import Linear (V2(..), V3(..), V4(..))
import qualified VulkanMemoryAllocator as VMA import qualified VulkanMemoryAllocator as VMA
import qualified Vulkan.Core10 as Vk import qualified Vulkan.Core10 as Vk
@ -37,14 +40,14 @@ loadMeshes
-> m () -> m ()
loadMeshes allocator uploadContext queue device = do loadMeshes allocator uploadContext queue device = do
let triangle = V.fromList let triangle = V.fromList
[ Vertex (V3 0.5 0.5 0) (V3 0 0 0) (V4 0 1 0 1) [ Vertex (V3 0.5 0.5 0) (V3 0 0 0) (V4 0 1 0 1) (V2 0 0)
, Vertex (V3 (-0.5) 0.5 0) (V3 0 0 0) (V4 0 1 0 1) , Vertex (V3 (-0.5) 0.5 0) (V3 0 0 0) (V4 0 1 0 1) (V2 0 0)
, Vertex (V3 0 (-0.5) 0) (V3 0 0 0) (V4 0 1 0 1) , Vertex (V3 0 (-0.5) 0) (V3 0 0 0) (V4 0 1 0 1) (V2 0 0)
] ]
triMesh <- uploadMesh triangle allocator uploadContext queue device triMesh <- uploadMesh triangle allocator uploadContext queue device
maskMesh <- loadFromObj maskMesh <- loadFromObj
"./assets/models/cat_mask_cyberpunk.obj" "./assets/models/jaeger.obj"
allocator allocator
uploadContext uploadContext
queue queue
@ -149,11 +152,12 @@ loadFromObj filepath vma uploadContext queue device = do
Left err -> Left err ->
error ("loadFromObj: loading mesh data: " <> err) error ("loadFromObj: loading mesh data: " <> err)
Right obj -> do Right obj -> do
let vertices = digestFaces (objFaces obj) (objLocations obj) let vertices = digestFaces (objFaces obj) (objLocations obj) (objTexCoords obj)
uploadMesh vertices vma uploadContext queue device uploadMesh vertices vma uploadContext queue device
where where
digestFaces :: V.Vector (Element Face) -> V.Vector Location -> V.Vector Vertex digestFaces
digestFaces faces locations = :: V.Vector (Element Face) -> V.Vector Location -> V.Vector TexCoord -> V.Vector Vertex
digestFaces faces locations texCoords =
V.foldl V.foldl
(\acc (Element _ _ _ _ (Face fa fb fc others)) -> (\acc (Element _ _ _ _ (Face fa fb fc others)) ->
if not (null others) if not (null others)
@ -165,8 +169,9 @@ loadFromObj filepath vma uploadContext queue device = do
let position = faceIndexToPosition faceIndex locations let position = faceIndexToPosition faceIndex locations
normal = V3 0 0 0 normal = V3 0 0 0
color = V4 1 1 0 1 color = V4 1 1 0 1
uv = faceIndexToUV faceIndex texCoords
in in
Vertex position normal color Vertex position normal color uv
) )
(V.fromList [ fa, fb, fc ]) (V.fromList [ fa, fb, fc ])
in in
@ -179,3 +184,10 @@ loadFromObj filepath vma uploadContext queue device = do
let Location x y z _ = locations V.! (faceLocIndex index - 1) let Location x y z _ = locations V.! (faceLocIndex index - 1)
in in
V3 x y z V3 x y z
faceIndexToUV :: FaceIndex -> V.Vector TexCoord -> V2 Float
faceIndexToUV index texCoords =
let TexCoord r s _ =
texCoords V.!
(fromMaybe (error "no UV coordinates present") (faceTexCoordIndex index) - 1)
in
V2 r s

View file

@ -152,7 +152,7 @@ loadImages
-> m () -> m ()
loadImages allocator uploadContext queue device = do loadImages allocator uploadContext queue device = do
loadedImage <- loadImageFromFile allocator uploadContext queue device "assets/textures/bricks.png" loadedImage <- loadImageFromFile allocator uploadContext queue device "assets/textures/jaeger.texture.tga"
let imageInfo = imageviewCreate (image loadedImage) Vk.FORMAT_R8G8B8A8_SRGB Vk.IMAGE_ASPECT_COLOR_BIT let imageInfo = imageviewCreate (image loadedImage) Vk.FORMAT_R8G8B8A8_SRGB Vk.IMAGE_ASPECT_COLOR_BIT
@ -168,6 +168,6 @@ loadImages allocator uploadContext queue device = do
void $ liftIO $ STM.atomically $ do void $ liftIO $ STM.atomically $ do
texMap <- STM.readTMVar textureLib texMap <- STM.readTMVar textureLib
let newMap = M.insert "bricks" texture texMap let newMap = M.insert "marksman" texture texMap
STM.swapTMVar textureLib newMap STM.swapTMVar textureLib newMap

View file

@ -40,6 +40,7 @@ data EngineData = EngineData
, engineFrames :: V.Vector FrameData , engineFrames :: V.Vector FrameData
, engineGlobalSetLayout :: Vk.DescriptorSetLayout , engineGlobalSetLayout :: Vk.DescriptorSetLayout
, engineObjectSetLayout :: Vk.DescriptorSetLayout , engineObjectSetLayout :: Vk.DescriptorSetLayout
, engineSingleTextureSetLayout :: Vk.DescriptorSetLayout
, engineDescriptorPool :: Vk.DescriptorPool , engineDescriptorPool :: Vk.DescriptorPool
, engineSceneParameters :: GPUSceneData , engineSceneParameters :: GPUSceneData
, engineUploadContext :: UploadContext , engineUploadContext :: UploadContext
@ -57,24 +58,30 @@ data Vertex = Vertex
{ vertexPosition :: V3 Float { vertexPosition :: V3 Float
, vertexNormal :: V3 Float , vertexNormal :: V3 Float
, vertexColor :: V4 Float , vertexColor :: V4 Float
, vertexUV :: V2 Float
} }
deriving (Show) deriving (Show)
instance Storable Vertex where instance Storable Vertex where
sizeOf _ = sizeOf (undefined :: V3 Float) * 2 + sizeOf (undefined :: V4 Float) sizeOf _ =
sizeOf (undefined :: V3 Float) * 2 +
sizeOf (undefined :: V4 Float) +
sizeOf (undefined :: V2 Float)
peek ptr = do peek ptr = do
pos <- peek (castPtr ptr) pos <- peek (castPtr ptr)
nor <- peek (castPtr ptr `plusPtr` sizeOf pos) nor <- peek (castPtr ptr `plusPtr` sizeOf pos)
col <- peek (castPtr ptr `plusPtr` sizeOf pos `plusPtr` sizeOf nor) col <- peek (castPtr ptr `plusPtr` sizeOf pos `plusPtr` sizeOf nor)
return $ Vertex pos nor col uv <- peek (castPtr ptr `plusPtr` sizeOf pos `plusPtr` sizeOf nor `plusPtr` sizeOf col)
return $ Vertex pos nor col uv
poke ptr (Vertex position normal color) = do poke ptr (Vertex position normal color uv) = do
let castedV3Ptr = castPtr ptr let castedV3Ptr = castPtr ptr
pokeElemOff castedV3Ptr 0 position pokeElemOff castedV3Ptr 0 position
pokeElemOff castedV3Ptr 1 normal pokeElemOff castedV3Ptr 1 normal
poke (castPtr (ptr `plusPtr` sizeOf position `plusPtr` sizeOf normal)) color poke (castPtr (ptr `plusPtr` sizeOf position `plusPtr` sizeOf normal)) color
poke (castPtr (ptr `plusPtr` sizeOf position `plusPtr` sizeOf normal `plusPtr` sizeOf color)) uv
alignment _ = 0 alignment _ = 0
@ -108,6 +115,13 @@ instance VertexInputDescribable Vertex where
, Vk.format = Vk.FORMAT_R32G32B32A32_SFLOAT , Vk.format = Vk.FORMAT_R32G32B32A32_SFLOAT
, Vk.offset = fromIntegral (sizeOf (vertexPosition v) + sizeOf (vertexNormal v)) , Vk.offset = fromIntegral (sizeOf (vertexPosition v) + sizeOf (vertexNormal v))
} :: Vk.VertexInputAttributeDescription } :: Vk.VertexInputAttributeDescription
uvAttribute = Vk.zero
{ Vk.binding = 0
, Vk.location = 3
, Vk.format = Vk.FORMAT_R32G32_SFLOAT
, Vk.offset = fromIntegral $
sizeOf (vertexPosition v) + sizeOf (vertexNormal v) + sizeOf (vertexColor v)
} :: Vk.VertexInputAttributeDescription
in in
VertexInputDescription VertexInputDescription
{ vidBindings = V.fromList [ mainBinding ] { vidBindings = V.fromList [ mainBinding ]
@ -115,6 +129,7 @@ instance VertexInputDescribable Vertex where
[ positionAttribute [ positionAttribute
, normalAttribute , normalAttribute
, colorAttribute , colorAttribute
, uvAttribute
] ]
} }
@ -161,7 +176,8 @@ data AllocatedImage = AllocatedImage
deriving (Show) deriving (Show)
data Material = Material data Material = Material
{ materialPipeline :: Vk.Pipeline { materialTextureSet :: Vk.DescriptorSet
, materialPipeline :: Vk.Pipeline
, materialPipelineLayout :: Vk.PipelineLayout , materialPipelineLayout :: Vk.PipelineLayout
} }
deriving (Show) deriving (Show)

View file

@ -80,3 +80,31 @@ createSubmitInfo cmd = V.singleton $ Vk.SomeStruct $
Vk.zero Vk.zero
{ Vk.commandBuffers = V.singleton (Vk.commandBufferHandle cmd) { Vk.commandBuffers = V.singleton (Vk.commandBufferHandle cmd)
} }
samplerCreateInfo
:: Vk.Filter
-> Vk.SamplerAddressMode
-> Vk.SamplerCreateInfo '[]
samplerCreateInfo filters addressMode =
Vk.zero
{ Vk.magFilter = filters
, Vk.minFilter = filters
, Vk.addressModeU = addressMode
, Vk.addressModeV = addressMode
, Vk.addressModeW = addressMode
}
writeDescriptorImage
:: Vk.DescriptorType
-> Vk.DescriptorSet
-> Vk.DescriptorImageInfo
-> Word32
-> Vk.WriteDescriptorSet '[]
writeDescriptorImage type' set imageInfo binding =
Vk.zero
{ Vk.dstBinding = binding
, Vk.dstSet = set
, Vk.descriptorCount = 1
, Vk.descriptorType = type'
, Vk.imageInfo = V.singleton imageInfo
}