{-# LANGUAGE OverloadedLists #-}

module Render.Skybox.Pipeline
  ( Config
  , config
  , Pipeline
  , allocate

  , stageCode
  , stageSpirv
  ) where

import RIO

import Control.Monad.Trans.Resource (ResourceT)
import Data.Tagged (Tagged(..))
import Vulkan.Core10 qualified as Vk

import Engine.Vulkan.Pipeline.Graphics qualified as Graphics
import Engine.Vulkan.Types (DsLayoutBindings, HasVulkan, HasRenderPass(..))
import Render.Code (compileVert, compileFrag)
import Render.DescSets.Set0 (Scene)
import Render.Skybox.Code qualified as Code

type Pipeline = Graphics.Pipeline '[Scene] () ()
type Config = Graphics.Configure Pipeline
type instance Graphics.Specialization Pipeline = ()

allocate
  :: ( HasVulkan env
     , HasRenderPass renderpass
     )
  => Vk.SampleCountFlagBits
  -> Tagged Scene DsLayoutBindings
  -> renderpass
  -> ResourceT (RIO env) Pipeline
allocate :: forall env renderpass.
(HasVulkan env, HasRenderPass renderpass) =>
SampleCountFlagBits
-> Tagged Scene DsLayoutBindings
-> renderpass
-> ResourceT (RIO env) Pipeline
allocate SampleCountFlagBits
multisample Tagged Scene DsLayoutBindings
tset0 = do
  forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. (a, b) -> b
snd forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall config pipeline (dsl :: [*]) vertices instances spec env
       (m :: * -> *) renderpass.
(config ~ Configure pipeline,
 pipeline ~ Pipeline dsl vertices instances,
 spec ~ Specialization pipeline, Specialization spec, HasCallStack,
 MonadVulkan env m, MonadResource m, HasRenderPass renderpass) =>
Maybe Extent2D
-> SampleCountFlagBits
-> Config dsl vertices instances spec
-> renderpass
-> m (ReleaseKey, pipeline)
Graphics.allocate
    forall a. Maybe a
Nothing
    SampleCountFlagBits
multisample
    (Tagged Scene DsLayoutBindings -> Configure Pipeline
config Tagged Scene DsLayoutBindings
tset0)

config :: Tagged Scene DsLayoutBindings -> Config
config :: Tagged Scene DsLayoutBindings -> Configure Pipeline
config (Tagged DsLayoutBindings
set0) = forall vertices instances. Config '[] vertices instances ()
Graphics.baseConfig
  { $sel:cStages:Config :: StageSpirv
Graphics.cStages      = StageSpirv
stageSpirv
  , $sel:cDescLayouts:Config :: Tagged '[Scene] [DsLayoutBindings]
Graphics.cDescLayouts = forall {k} (s :: k) b. b -> Tagged s b
Tagged @'[Scene] [DsLayoutBindings
set0]
  , $sel:cCull:Config :: CullModeFlagBits
Graphics.cCull        = CullModeFlagBits
Vk.CULL_MODE_NONE
  }

stageCode :: Graphics.StageCode
stageCode :: StageCode
stageCode = forall a.
("vert" ::: a) -> ("vert" ::: a) -> Stages (Maybe ("vert" ::: a))
Graphics.basicStages Code
Code.vert Code
Code.frag

stageSpirv :: Graphics.StageSpirv
stageSpirv :: StageSpirv
stageSpirv = forall a.
("vert" ::: a) -> ("vert" ::: a) -> Stages (Maybe ("vert" ::: a))
Graphics.basicStages ByteString
vertSpirv ByteString
fragSpirv

vertSpirv :: ByteString
vertSpirv :: ByteString
vertSpirv = $(compileVert Code.vert)

fragSpirv :: ByteString
fragSpirv :: ByteString
fragSpirv = $(compileFrag Code.frag)