Skip to content

Commit

Permalink
Display initialization progress
Browse files Browse the repository at this point in the history
  • Loading branch information
fwcd committed Oct 14, 2024
1 parent cd9e80a commit 4c23cf9
Showing 1 changed file with 11 additions and 1 deletion.
12 changes: 11 additions & 1 deletion src/Curry/LanguageServer/Handlers/Initialized.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
{-# LANGUAGE OverloadedStrings #-}
module Curry.LanguageServer.Handlers.Initialized (initializedHandler) where

import Control.Monad (void, forM_)
import Curry.LanguageServer.FileLoader (fileLoader)
import Curry.LanguageServer.Handlers.Diagnostics (emitDiagnostics)
import Curry.LanguageServer.Utils.Logging (infoM)
Expand All @@ -11,13 +12,22 @@ import qualified Data.Text as T
import qualified Language.LSP.Server as S
import qualified Language.LSP.Protocol.Types as J
import qualified Language.LSP.Protocol.Message as J
import System.FilePath (takeFileName)

initializedHandler :: S.Handlers LSM
initializedHandler = S.notificationHandler J.SMethod_Initialized $ \_nt -> do
infoM "Building index store..."
workspaceFolders <- fromMaybe [] <$> S.getWorkspaceFolders
let folders = maybeToList . folderToPath =<< workspaceFolders
mapM_ addDirToIndexStore folders
folderCount = length folders

void $ S.withProgress "Curry: Adding folders" Nothing S.Cancellable $ \update ->
forM_ (zip [0..] folders) $ \(i, fp) -> do
let percent = (i * 100) `div` folderCount
msg = T.pack $ "[" ++ show (i + 1) ++ " of " ++ show folderCount ++ "] " ++ takeFileName fp
update (S.ProgressAmount (Just $ fromIntegral percent) $ Just msg)
addDirToIndexStore fp

count <- I.getModuleCount
infoM $ "Indexed " <> T.pack (show count) <> " files"
where folderToPath (J.WorkspaceFolder uri _) = J.uriToFilePath uri
Expand Down

0 comments on commit 4c23cf9

Please sign in to comment.