module Render.Lit.Colored.Pipeline
  ( Pipeline
  , allocate
  , allocateBlend

  , Config
  , config
  , configBlend
  ) 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.Types (HasVulkan, HasRenderPass(..), DsBindings)
import Render.Code (compileVert, compileFrag, glsl)
import Render.Code.Lit (litMain, structLight, shadowFuns, brdfSpecular)
import Render.DescSets.Set0 (Scene, vertexPos, instanceTransform)
import Render.DescSets.Set0.Code (set0binding0, set0binding1, set0binding2, set0binding3, set0binding4, set0binding5)
import Render.Lit.Colored.Model qualified as Model

type Config = Pipeline.Configure Pipeline ()
type Pipeline = Pipeline.Pipeline '[Scene] Model.VertexAttrs Model.InstanceAttrs

allocate
  :: ( HasVulkan env
     , HasRenderPass renderpass
     )
  => Vk.SampleCountFlagBits
  -> Tagged Scene DsBindings
  -> renderpass
  -> ResourceT (RIO env) Pipeline
allocate :: forall env renderpass.
(HasVulkan env, HasRenderPass renderpass) =>
SampleCountFlagBits
-> Tagged Scene DsBindings
-> renderpass
-> ResourceT (RIO env) Pipeline
allocate SampleCountFlagBits
multisample Tagged Scene DsBindings
tset0 renderpass
rp = do
  (ReleaseKey
_, Pipeline
p) <- Maybe Extent2D
-> SampleCountFlagBits
-> Config '[Scene] VertexAttrs InstanceAttrs ()
-> renderpass
-> ResourceT (RIO env) (ReleaseKey, Pipeline)
forall env (m :: * -> *) renderpass spec (dsl :: [*]) vertices
       instances.
(MonadVulkan env m, MonadResource m, HasRenderPass renderpass,
 Specialization spec, HasCallStack) =>
Maybe Extent2D
-> SampleCountFlagBits
-> Config dsl vertices instances spec
-> renderpass
-> m (ReleaseKey, Pipeline dsl vertices instances)
Pipeline.allocate
    Maybe Extent2D
forall a. Maybe a
Nothing
    SampleCountFlagBits
multisample
    (Tagged Scene DsBindings -> Config
config Tagged Scene DsBindings
tset0)
    renderpass
rp
  Pipeline -> ResourceT (RIO env) Pipeline
forall (f :: * -> *) a. Applicative f => a -> f a
pure Pipeline
p

allocateBlend
  :: ( HasVulkan env
     , HasRenderPass renderpass
     )
  => Vk.SampleCountFlagBits
  -> Tagged Scene DsBindings
  -> renderpass
  -> ResourceT (RIO env) Pipeline
allocateBlend :: forall env renderpass.
(HasVulkan env, HasRenderPass renderpass) =>
SampleCountFlagBits
-> Tagged Scene DsBindings
-> renderpass
-> ResourceT (RIO env) Pipeline
allocateBlend SampleCountFlagBits
multisample Tagged Scene DsBindings
tset0 renderpass
rp = do
  (ReleaseKey
_, Pipeline
p) <- Maybe Extent2D
-> SampleCountFlagBits
-> Config '[Scene] VertexAttrs InstanceAttrs ()
-> renderpass
-> ResourceT (RIO env) (ReleaseKey, Pipeline)
forall env (m :: * -> *) renderpass spec (dsl :: [*]) vertices
       instances.
(MonadVulkan env m, MonadResource m, HasRenderPass renderpass,
 Specialization spec, HasCallStack) =>
Maybe Extent2D
-> SampleCountFlagBits
-> Config dsl vertices instances spec
-> renderpass
-> m (ReleaseKey, Pipeline dsl vertices instances)
Pipeline.allocate
    Maybe Extent2D
forall a. Maybe a
Nothing
    SampleCountFlagBits
multisample
    (Tagged Scene DsBindings -> Config
configBlend Tagged Scene DsBindings
tset0)
    renderpass
rp
  Pipeline -> ResourceT (RIO env) Pipeline
forall (f :: * -> *) a. Applicative f => a -> f a
pure Pipeline
p

config :: Tagged Scene DsBindings -> Config
config :: Tagged Scene DsBindings -> Config
config (Tagged DsBindings
set0) = Config '[] Any Any ()
forall vertices instances. Config '[] vertices instances ()
Pipeline.baseConfig
  { $sel:cDescLayouts:Config :: Tagged '[Scene] [DsBindings]
Pipeline.cDescLayouts  = forall {s :: [*]} {b}. b -> Tagged s b
forall {k} (s :: k) b. b -> Tagged s b
Tagged @'[Scene] [DsBindings
set0]
  , $sel:cVertexCode:Config :: Maybe ByteString
Pipeline.cVertexCode   = ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
vertCode
  , $sel:cVertexInput:Config :: SomeStruct PipelineVertexInputStateCreateInfo
Pipeline.cVertexInput  = SomeStruct PipelineVertexInputStateCreateInfo
vertexInput
  , $sel:cFragmentCode:Config :: Maybe ByteString
Pipeline.cFragmentCode = ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
fragCode
  }
  where
    vertexInput :: SomeStruct PipelineVertexInputStateCreateInfo
vertexInput = [(VertexInputRate, [Format])]
-> SomeStruct PipelineVertexInputStateCreateInfo
Pipeline.vertexInput
      [ (VertexInputRate, [Format])
vertexPos
      , (VertexInputRate
Vk.VERTEX_INPUT_RATE_VERTEX, [Format]
Model.vkVertexAttrs)
      , (VertexInputRate, [Format])
instanceTransform
      ]

configBlend :: Tagged Scene DsBindings -> Config
configBlend :: Tagged Scene DsBindings -> Config
configBlend Tagged Scene DsBindings
tset0 = (Tagged Scene DsBindings -> Config
config Tagged Scene DsBindings
tset0)
  { $sel:cBlend:Config :: Bool
Pipeline.cBlend = Bool
True
  }

vertCode :: ByteString
vertCode :: ByteString
vertCode =
  $(compileVert [glsl|
    #version 450
    #extension GL_ARB_separate_shader_objects : enable

    invariant gl_Position;

    ${set0binding0}

    layout(location = 0) in vec3 vPosition;
    layout(location = 1) in vec4 vBaseColor;
    layout(location = 2) in vec4 vEmissiveColor;
    layout(location = 3) in vec2 vMetallicRoughness;
    layout(location = 4) in vec3 vNormal;

    layout(location = 5) in mat4 iModel;

    layout(location = 0) out vec4 fPosition;
    layout(location = 1) out vec4 fColor;
    layout(location = 2) out vec4 fEmissiveColor;
    layout(location = 3) out vec2 fMetallicRoughness;
    layout(location = 4) out vec3 fNormal;

    void main() {
      fPosition = iModel * vec4(vPosition, 1.0);

      gl_Position
        = scene.projection
        * scene.view
        * fPosition;

      fNormal = transpose(mat3(inverse(iModel))) * vNormal; // TODO: use modelInv

      fColor = vBaseColor;
      fColor.rgb *= vBaseColor.a;

      fEmissiveColor = vEmissiveColor;
      fMetallicRoughness = vMetallicRoughness;
    }
  |])

fragCode :: ByteString
fragCode :: ByteString
fragCode =
  $(compileFrag [glsl|
    #version 450
    #extension GL_ARB_separate_shader_objects : enable
    #extension GL_EXT_nonuniform_qualifier : enable

    layout(early_fragment_tests) in;

    // TODO: move to spec constant
    const uint MAX_LIGHTS = 255;
    const float PCF_STEP = 1.5 / 4096;

    // TODO: move to material
    const float reflectivity = 1.0/256.0;

    ${structLight}

    ${set0binding0}
    ${set0binding1}
    ${set0binding2}
    ${set0binding3}
    ${set0binding4}
    ${set0binding5}

    layout(location = 0) in vec4 fPosition;
    layout(location = 1) in vec4 fColor;
    layout(location = 2) in vec4 fEmissiveColor;
    layout(location = 3) in vec2 fMetallicRoughness;
    layout(location = 4) in vec3 fNormal;

    layout(location = 0) out vec4 oColor;

    ${shadowFuns}
    ${brdfSpecular}

    void main() {
      vec4 baseColor = fColor; // XXX: assuming premultiplied alpha
      float metallic = fMetallicRoughness[0];
      float roughness = fMetallicRoughness[1];
      float nonOcclusion = 1.0;

      vec3 normal = normalize(fNormal);

      ${litMain}

      oColor.rgb += pow(fEmissiveColor.rgb, vec3(2.2));
    }
  |])