Skip to content

Commit 5ee9e28

Browse files
committed
Extract ghcide notification handlers to an HLS plugin
This is required to allow for user defined notification handlers, otherwise HLS plugins will overwrite the ghcide handlers and nothing will work
1 parent 1059338 commit 5ee9e28

File tree

3 files changed

+36
-34
lines changed

3 files changed

+36
-34
lines changed

ghcide/src/Development/IDE/LSP/LanguageServer.hs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -100,7 +100,6 @@ runLanguageServer options getHieDbLoc onConfigurationChange userHandlers getIdeS
100100
let ideHandlers = mconcat
101101
[ setIdeHandlers
102102
, userHandlers
103-
, setHandlersNotifications -- absolutely critical, join them with user notifications
104103
]
105104

106105
-- Send everything over a channel, since you need to wait until after initialise before

ghcide/src/Development/IDE/LSP/Notifications.hs

Lines changed: 21 additions & 20 deletions
Original file line numberDiff line numberDiff line change
@@ -7,8 +7,8 @@
77
{-# LANGUAGE RankNTypes #-}
88

99
module Development.IDE.LSP.Notifications
10-
( setHandlersNotifications
11-
, whenUriFile
10+
( whenUriFile
11+
, descriptor
1212
) where
1313

1414
import qualified Language.LSP.Server as LSP
@@ -38,15 +38,15 @@ import Development.IDE.Core.FileStore (resetFileStore,
3838
typecheckParents)
3939
import Development.IDE.Core.OfInterest
4040
import Ide.Plugin.Config (CheckParents (CheckOnClose))
41-
41+
import Ide.Types
4242

4343
whenUriFile :: Uri -> (NormalizedFilePath -> IO ()) -> IO ()
4444
whenUriFile uri act = whenJust (LSP.uriToFilePath uri) $ act . toNormalizedFilePath'
4545

46-
setHandlersNotifications :: LSP.Handlers (ServerM c)
47-
setHandlersNotifications = mconcat
48-
[ notificationHandler LSP.STextDocumentDidOpen $
49-
\ide (DidOpenTextDocumentParams TextDocumentItem{_uri,_version}) -> liftIO $ do
46+
descriptor :: PluginId -> PluginDescriptor IdeState
47+
descriptor plId = (defaultPluginDescriptor plId) { pluginNotificationHandlers = mconcat
48+
[ mkPluginNotificationHandler LSP.STextDocumentDidOpen $
49+
\ide _ (DidOpenTextDocumentParams TextDocumentItem{_uri,_version}) -> liftIO $ do
5050
updatePositionMapping ide (VersionedTextDocumentIdentifier _uri (Just _version)) (List [])
5151
whenUriFile _uri $ \file -> do
5252
-- We don't know if the file actually exists, or if the contents match those on disk
@@ -55,32 +55,32 @@ setHandlersNotifications = mconcat
5555
setFileModified ide False file
5656
logDebug (ideLogger ide) $ "Opened text document: " <> getUri _uri
5757

58-
, notificationHandler LSP.STextDocumentDidChange $
59-
\ide (DidChangeTextDocumentParams identifier@VersionedTextDocumentIdentifier{_uri} changes) -> liftIO $ do
58+
, mkPluginNotificationHandler LSP.STextDocumentDidChange $
59+
\ide _ (DidChangeTextDocumentParams identifier@VersionedTextDocumentIdentifier{_uri} changes) -> liftIO $ do
6060
updatePositionMapping ide identifier changes
6161
whenUriFile _uri $ \file -> do
6262
modifyFilesOfInterest ide (M.insert file Modified{firstOpen=False})
6363
setFileModified ide False file
6464
logDebug (ideLogger ide) $ "Modified text document: " <> getUri _uri
6565

66-
, notificationHandler LSP.STextDocumentDidSave $
67-
\ide (DidSaveTextDocumentParams TextDocumentIdentifier{_uri} _) -> liftIO $ do
66+
, mkPluginNotificationHandler LSP.STextDocumentDidSave $
67+
\ide _ (DidSaveTextDocumentParams TextDocumentIdentifier{_uri} _) -> liftIO $ do
6868
whenUriFile _uri $ \file -> do
6969
modifyFilesOfInterest ide (M.insert file OnDisk)
7070
setFileModified ide True file
7171
logDebug (ideLogger ide) $ "Saved text document: " <> getUri _uri
7272

73-
, notificationHandler LSP.STextDocumentDidClose $
74-
\ide (DidCloseTextDocumentParams TextDocumentIdentifier{_uri}) -> liftIO $ do
73+
, mkPluginNotificationHandler LSP.STextDocumentDidClose $
74+
\ide _ (DidCloseTextDocumentParams TextDocumentIdentifier{_uri}) -> liftIO $ do
7575
whenUriFile _uri $ \file -> do
7676
modifyFilesOfInterest ide (M.delete file)
7777
-- Refresh all the files that depended on this
7878
checkParents <- optCheckParents =<< getIdeOptionsIO (shakeExtras ide)
7979
when (checkParents >= CheckOnClose) $ typecheckParents ide file
8080
logDebug (ideLogger ide) $ "Closed text document: " <> getUri _uri
8181

82-
, notificationHandler LSP.SWorkspaceDidChangeWatchedFiles $
83-
\ide (DidChangeWatchedFilesParams (List fileEvents)) -> liftIO $ do
82+
, mkPluginNotificationHandler LSP.SWorkspaceDidChangeWatchedFiles $
83+
\ide _ (DidChangeWatchedFilesParams (List fileEvents)) -> liftIO $ do
8484
-- See Note [File existence cache and LSP file watchers] which explains why we get these notifications and
8585
-- what we do with them
8686
let msg = Text.pack $ show fileEvents
@@ -89,22 +89,22 @@ setHandlersNotifications = mconcat
8989
resetFileStore ide fileEvents
9090
setSomethingModified ide
9191

92-
, notificationHandler LSP.SWorkspaceDidChangeWorkspaceFolders $
93-
\ide (DidChangeWorkspaceFoldersParams events) -> liftIO $ do
92+
, mkPluginNotificationHandler LSP.SWorkspaceDidChangeWorkspaceFolders $
93+
\ide _ (DidChangeWorkspaceFoldersParams events) -> liftIO $ do
9494
let add = S.union
9595
substract = flip S.difference
9696
modifyWorkspaceFolders ide
9797
$ add (foldMap (S.singleton . parseWorkspaceFolder) (_added events))
9898
. substract (foldMap (S.singleton . parseWorkspaceFolder) (_removed events))
9999

100-
, notificationHandler LSP.SWorkspaceDidChangeConfiguration $
101-
\ide (DidChangeConfigurationParams cfg) -> liftIO $ do
100+
, mkPluginNotificationHandler LSP.SWorkspaceDidChangeConfiguration $
101+
\ide _ (DidChangeConfigurationParams cfg) -> liftIO $ do
102102
let msg = Text.pack $ show cfg
103103
logDebug (ideLogger ide) $ "Configuration changed: " <> msg
104104
modifyClientSettings ide (const $ Just cfg)
105105
setSomethingModified ide
106106

107-
, notificationHandler LSP.SInitialized $ \ide _ -> do
107+
, mkPluginNotificationHandler LSP.SInitialized $ \ide _ _ -> do
108108
clientCapabilities <- LSP.getClientCapabilities
109109
let watchSupported = case () of
110110
_ | LSP.ClientCapabilities{_workspace} <- clientCapabilities
@@ -139,3 +139,4 @@ setHandlersNotifications = mconcat
139139
void $ LSP.sendRequest SClientRegisterCapability regParams (const $ pure ()) -- TODO handle response
140140
else liftIO $ logDebug (ideLogger ide) "Warning: Client does not support watched files. Falling back to OS polling"
141141
]
142+
}

ghcide/src/Development/IDE/Plugin/HLS/GhcIde.hs

Lines changed: 15 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -1,29 +1,31 @@
11
{-# LANGUAGE DuplicateRecordFields #-}
2-
{-# LANGUAGE OverloadedStrings #-}
2+
{-# LANGUAGE OverloadedStrings #-}
33

44
-- | Exposes the ghcide features as an HLS plugin
55
module Development.IDE.Plugin.HLS.GhcIde
66
(
77
descriptors
88
) where
9-
import Development.IDE
10-
import Development.IDE.LSP.HoverDefinition
11-
import Development.IDE.LSP.Outline
12-
import Ide.Types
13-
import Language.LSP.Types
14-
import Language.LSP.Server (LspM)
15-
import Text.Regex.TDFA.Text()
16-
import qualified Development.IDE.Plugin.CodeAction as CodeAction
17-
import qualified Development.IDE.Plugin.Completions as Completions
18-
import qualified Development.IDE.Plugin.TypeLenses as TypeLenses
19-
import Control.Monad.IO.Class
9+
import Control.Monad.IO.Class
10+
import Development.IDE
11+
import Development.IDE.LSP.HoverDefinition
12+
import qualified Development.IDE.LSP.Notifications as Notifications
13+
import Development.IDE.LSP.Outline
14+
import qualified Development.IDE.Plugin.CodeAction as CodeAction
15+
import qualified Development.IDE.Plugin.Completions as Completions
16+
import qualified Development.IDE.Plugin.TypeLenses as TypeLenses
17+
import Ide.Types
18+
import Language.LSP.Server (LspM)
19+
import Language.LSP.Types
20+
import Text.Regex.TDFA.Text ()
2021

2122
descriptors :: [PluginDescriptor IdeState]
2223
descriptors =
2324
[ descriptor "ghcide-hover-and-symbols",
2425
CodeAction.descriptor "ghcide-code-actions",
2526
Completions.descriptor "ghcide-completions",
26-
TypeLenses.descriptor "ghcide-type-lenses"
27+
TypeLenses.descriptor "ghcide-type-lenses",
28+
Notifications.descriptor "ghcide-core"
2729
]
2830

2931
-- ---------------------------------------------------------------------

0 commit comments

Comments
 (0)