Skip to content

Commit

Permalink
Asynchronously build index store
Browse files Browse the repository at this point in the history
  • Loading branch information
fwcd committed Oct 14, 2024
1 parent edb4689 commit eae0c31
Showing 1 changed file with 14 additions and 9 deletions.
23 changes: 14 additions & 9 deletions src/Curry/LanguageServer/Handlers/Initialized.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,10 @@
{-# LANGUAGE OverloadedStrings #-}
module Curry.LanguageServer.Handlers.Initialized (initializedHandler) where

import Control.Monad (void, forM_)
import Control.Concurrent (forkIO)
import Control.Monad (forM_, void)
import Control.Monad.IO.Class (liftIO)
import Control.Monad.IO.Unlift (askRunInIO)
import Curry.LanguageServer.FileLoader (fileLoader)
import Curry.LanguageServer.Handlers.Diagnostics (emitDiagnostics)
import Curry.LanguageServer.Utils.Logging (infoM)
Expand All @@ -16,21 +19,23 @@ 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
folderCount = length folders
runInIO <- askRunInIO
void $ liftIO $ forkIO $ runInIO $ S.withProgress "Curry: Adding folders" Nothing S.NotCancellable $ \update -> do
infoM "Building index store..."
workspaceFolders <- fromMaybe [] <$> S.getWorkspaceFolders

let folders = maybeToList . folderToPath =<< workspaceFolders
folderCount = length folders

void $ S.withProgress "Curry: Adding folders" Nothing S.NotCancellable $ \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
count <- I.getModuleCount
infoM $ "Indexed " <> T.pack (show count) <> " files"
where folderToPath (J.WorkspaceFolder uri _) = J.uriToFilePath uri

-- | Indexes a workspace folder recursively.
addDirToIndexStore :: FilePath -> LSM ()
Expand Down

0 comments on commit eae0c31

Please sign in to comment.