Skip to content

Commit

Permalink
Move diagnostic reporting back into the initialized notification handler
Browse files Browse the repository at this point in the history
  • Loading branch information
fwcd committed Oct 14, 2024
1 parent 31f5f6f commit a32946e
Show file tree
Hide file tree
Showing 2 changed files with 8 additions and 4 deletions.
2 changes: 2 additions & 0 deletions src/Curry/LanguageServer/Handlers.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
module Curry.LanguageServer.Handlers (handlers) where

import Curry.LanguageServer.Handlers.Cancel (cancelHandler)
import Curry.LanguageServer.Handlers.Initialize (initializedHandler)
import Curry.LanguageServer.Handlers.TextDocument.CodeAction (codeActionHandler)
import Curry.LanguageServer.Handlers.TextDocument.CodeLens (codeLensHandler)
import Curry.LanguageServer.Handlers.TextDocument.Completion (completionHandler)
Expand Down Expand Up @@ -29,6 +30,7 @@ handlers _caps = mconcat
, codeLensHandler
, signatureHelpHandler
-- Notification handlers
, initializedHandler
, didOpenHandler
, didChangeHandler
, didSaveHandler
Expand Down
10 changes: 6 additions & 4 deletions src/Curry/LanguageServer/Handlers/Initialize.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
{-# LANGUAGE DataKinds, OverloadedStrings #-}
module Curry.LanguageServer.Handlers.Initialize (initializeHandler) where
module Curry.LanguageServer.Handlers.Initialize (initializeHandler, initializedHandler) where

import Control.Lens ((^.))
import Curry.LanguageServer.FileLoader (fileLoader)
Expand All @@ -26,12 +26,14 @@ initializeHandler req = do
count <- I.getModuleCount
infoM $ "Indexed " <> T.pack (show count) <> " files"

initializedHandler :: S.Handlers LSM
initializedHandler = S.notificationHandler J.SMethod_Initialized $ \_nt -> do
entries <- I.getModuleList
mapM_ (uncurry emitDiagnostics) entries

-- | Indexes a workspace folder recursively.
addDirToIndexStore :: FilePath -> LSM ()
addDirToIndexStore dirPath = do
fl <- fileLoader
cfg <- S.getConfig
I.addWorkspaceDir cfg fl dirPath
entries <- I.getModuleList
mapM_ (uncurry emitDiagnostics) entries

0 comments on commit a32946e

Please sign in to comment.