{-# LANGUAGE OverloadedLists #-} -- XXX: TypeError in Compatible generates unused constraint argument {-# OPTIONS_GHC -Wno-redundant-constraints #-} module Engine.Vulkan.Pipeline.Compute ( Config(..) , Configure , Pipeline(..) , allocate , create , destroy , bind , Compute ) where import RIO import Data.Kind (Type) import Data.List qualified as List import Data.Tagged (Tagged(..)) import Data.Vector qualified as Vector import GHC.Stack (callStack, getCallStack, srcLocModule, withFrozenCallStack) import UnliftIO.Resource (MonadResource, ReleaseKey) import UnliftIO.Resource qualified as Resource import Vulkan.Core10 qualified as Vk import Vulkan.Core12.Promoted_From_VK_EXT_descriptor_indexing qualified as Vk12 import Vulkan.CStruct.Extends (SomeStruct(..), pattern (:&), pattern (::&)) import Vulkan.Utils.Debug qualified as Debug import Vulkan.Zero (Zero(..)) import Engine.Vulkan.DescSets (Bound(..), Compatible) import Engine.Vulkan.Types (HasVulkan(..), MonadVulkan, DsBindings, getPipelineCache) import Engine.Vulkan.Pipeline (Pipeline(..), destroy) import Engine.Vulkan.Shader qualified as Shader data Config (dsl :: [Type]) spec = Config { cComputeCode :: ByteString , cDescLayouts :: Tagged dsl [DsBindings] , cPushConstantRanges :: Vector Vk.PushConstantRange , cSpecialization :: spec } data Compute type family Configure pipeline spec where Configure (Pipeline dsl Compute Compute) spec = Config dsl spec allocate :: ( MonadVulkan env m , MonadResource m , HasCallStack , Shader.Specialization spec ) => Config dsl spec -> m (ReleaseKey, Pipeline dsl Compute Compute) allocate config = withFrozenCallStack do ctx <- ask Resource.allocate (create ctx config) (destroy ctx) create :: ( HasVulkan ctx , MonadUnliftIO m , Shader.Specialization spec ) => ctx -> Config dsl spec -> m (Pipeline dsl Compute Compute) create context Config{..} = do -- XXX: copypasta from Pipeline.create let originModule = fromString . List.intercalate "|" $ map (srcLocModule . snd) (getCallStack callStack) dsLayouts <- Vector.forM (Vector.fromList $ unTagged cDescLayouts) \bindsFlags -> do let (binds, flags) = List.unzip bindsFlags setCI = zero { Vk.bindings = Vector.fromList binds } ::& zero { Vk12.bindingFlags = Vector.fromList flags } :& () Vk.createDescriptorSetLayout device setCI Nothing -- TODO: get from outside layout <- Vk.createPipelineLayout device (layoutCI dsLayouts) Nothing Debug.nameObject device layout originModule -- Compute stuff begins... shader <- Shader.withSpecialization cSpecialization $ Shader.create context [(Vk.SHADER_STAGE_COMPUTE_BIT, cComputeCode)] let cis = Vector.singleton . SomeStruct $ pipelineCI (Shader.sPipelineStages shader) layout Vk.createComputePipelines device cache cis Nothing >>= \case (Vk.SUCCESS, pipelines) -> case pipelines of [one] -> do Shader.destroy context shader Debug.nameObject device one originModule pure Pipeline { pipeline = one , pLayout = Tagged layout , pDescLayouts = Tagged dsLayouts } _ -> error "assert: exactly one pipeline requested" (err, _) -> throwString $ "createComputePipelines: " <> show err where device = getDevice context cache = getPipelineCache context layoutCI dsLayouts = Vk.PipelineLayoutCreateInfo { flags = zero , setLayouts = dsLayouts , pushConstantRanges = cPushConstantRanges } pipelineCI stages layout = zero { Vk.layout = layout , Vk.stage = stage , Vk.basePipelineHandle = zero } where stage = case stages of [one] -> one _assert -> error "compute code has one stage" bind :: ( Compatible pipeLayout boundLayout , MonadIO m ) => Vk.CommandBuffer -> Pipeline pipeLayout vertices instances -> Bound boundLayout vertices instances m () -> Bound boundLayout oldVertices oldInstances m () bind cb Pipeline{pipeline} (Bound attrAction) = do Bound $ Vk.cmdBindPipeline cb Vk.PIPELINE_BIND_POINT_COMPUTE pipeline Bound attrAction