module Render.Debug.Pipeline ( Pipeline , allocate , Mode(..) ) where import RIO import Control.Monad.Trans.Resource (ResourceT) import Data.Tagged (Tagged(..)) import Vulkan.Core10 qualified as Vk import Engine.Vulkan.Pipeline qualified as Pipeline import Engine.Vulkan.Shader qualified as Shader import Engine.Vulkan.Types (HasVulkan, HasRenderPass(..), DsBindings) import Render.Code (compileVert, compileFrag, glsl) import Render.Debug.Model qualified as Model import Render.DescSets.Set0 (Scene, vertexPos, instanceTransform) import Render.DescSets.Set0.Code (set0binding0, set0binding1, set0binding2, set0binding3, set0binding5color) type Pipeline = Pipeline.Pipeline '[Scene] Model.VertexAttrs Model.InstanceAttrs data Mode = UV | Texture | Shadow Word32 deriving (Eq, Ord, Show) instance Shader.Specialization Mode where specializationData = \case UV -> [0] Texture -> [1] Shadow bits -> [2, bits] allocate :: ( HasVulkan env , HasRenderPass renderpass ) => Mode -> Vk.SampleCountFlagBits -> Tagged Scene DsBindings -> renderpass -> ResourceT (RIO env) Pipeline allocate mode multisample (Tagged set0) = do fmap snd . Pipeline.allocate Nothing multisample config where config = Pipeline.baseConfig { Pipeline.cDescLayouts = Tagged @'[Scene] [set0] , Pipeline.cVertexCode = Just vertCode , Pipeline.cVertexInput = vertexInput , Pipeline.cFragmentCode = Just fragCode , Pipeline.cSpecialization = mode } vertexInput = Pipeline.vertexInput [ vertexPos -- vPosition , (Vk.VERTEX_INPUT_RATE_VERTEX, Model.vkVertexAttrs) , (Vk.VERTEX_INPUT_RATE_INSTANCE, Model.vkInstanceTexture) , instanceTransform ] vertCode :: ByteString vertCode = $(compileVert [glsl| #version 450 #extension GL_ARB_separate_shader_objects : enable ${set0binding0} // vertexPos layout(location = 0) in vec3 vPosition; // vertexAttrs layout(location = 1) in vec2 vTexCoord; // textureParams layout(location = 2) in vec4 iTextureScaleOffset; layout(location = 3) in vec4 iTextureGamma; layout(location = 4) in ivec2 iTextureIds; // transformMat layout(location = 5) in mat4 iModel; layout(location = 0) out vec2 fTexCoord; layout(location = 1) flat out vec4 fTextureGamma; layout(location = 2) flat out ivec2 fTextureIds; void main() { vec4 fPosition = iModel * vec4(vPosition, 1.0); gl_Position = scene.projection * scene.view * fPosition; fTexCoord = vTexCoord * iTextureScaleOffset.st + iTextureScaleOffset.pq; fTextureGamma = iTextureGamma; fTextureIds = iTextureIds; } |]) fragCode :: ByteString fragCode = $(compileFrag [glsl| #version 450 #extension GL_ARB_separate_shader_objects : enable #extension GL_EXT_nonuniform_qualifier : enable ${set0binding1} ${set0binding2} ${set0binding3} ${set0binding5color} layout(location = 0) in vec2 fTexCoord; layout(location = 1) flat in vec4 fTextureGamma; layout(location = 2) flat in ivec2 fTextureIds; layout(location = 0) out vec4 oColor; layout (constant_id=0) const uint mode = 0; layout (constant_id=1) const uint shadow_mask = 0; void main() { vec4 texel = vec4(0); switch(mode) { case 0: texel = vec4(fTexCoord, 0, 1); break; case 1: if ((fTextureIds.t < 0) || (fTextureIds.s < 0)) break; texel = texture( sampler2D( textures[nonuniformEXT(fTextureIds.t)], samplers[nonuniformEXT(fTextureIds.s)] ), fTexCoord ); break; case 2: float d0 = 1.0; if ((shadow_mask & 1) == 1) d0 = texture( shadowmaps, vec3(fTexCoord, 0.0) ).x; float d1 = 1.0; if ((shadow_mask & 2) == 2) d1 = texture( shadowmaps, vec3(fTexCoord, 1.0) ).x; float d2 = 1.0; if ((shadow_mask & 4) == 4) d2 = texture( shadowmaps, vec3(fTexCoord, 2.0) ).x; texel = vec4(1-d0, 1-d1, 1-d2, 1.0); break; default: break; } vec3 color = pow(texel.rgb, fTextureGamma.rgb); float combinedAlpha = texel.a * fTextureGamma.a; // XXX: premultiply alpha due to additive blending oColor = vec4(color * combinedAlpha, combinedAlpha); } |])