7
7
{-# LANGUAGE RankNTypes #-}
8
8
9
9
module Development.IDE.LSP.Notifications
10
- ( setHandlersNotifications
11
- , whenUriFile
10
+ ( whenUriFile
11
+ , descriptor
12
12
) where
13
13
14
14
import qualified Language.LSP.Server as LSP
@@ -38,15 +38,15 @@ import Development.IDE.Core.FileStore (resetFileStore,
38
38
typecheckParents )
39
39
import Development.IDE.Core.OfInterest
40
40
import Ide.Plugin.Config (CheckParents (CheckOnClose ))
41
-
41
+ import Ide.Types
42
42
43
43
whenUriFile :: Uri -> (NormalizedFilePath -> IO () ) -> IO ()
44
44
whenUriFile uri act = whenJust (LSP. uriToFilePath uri) $ act . toNormalizedFilePath'
45
45
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
50
50
updatePositionMapping ide (VersionedTextDocumentIdentifier _uri (Just _version)) (List [] )
51
51
whenUriFile _uri $ \ file -> do
52
52
-- We don't know if the file actually exists, or if the contents match those on disk
@@ -55,32 +55,32 @@ setHandlersNotifications = mconcat
55
55
setFileModified ide False file
56
56
logDebug (ideLogger ide) $ " Opened text document: " <> getUri _uri
57
57
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
60
60
updatePositionMapping ide identifier changes
61
61
whenUriFile _uri $ \ file -> do
62
62
modifyFilesOfInterest ide (M. insert file Modified {firstOpen= False })
63
63
setFileModified ide False file
64
64
logDebug (ideLogger ide) $ " Modified text document: " <> getUri _uri
65
65
66
- , notificationHandler LSP. STextDocumentDidSave $
67
- \ ide (DidSaveTextDocumentParams TextDocumentIdentifier {_uri} _) -> liftIO $ do
66
+ , mkPluginNotificationHandler LSP. STextDocumentDidSave $
67
+ \ ide _ (DidSaveTextDocumentParams TextDocumentIdentifier {_uri} _) -> liftIO $ do
68
68
whenUriFile _uri $ \ file -> do
69
69
modifyFilesOfInterest ide (M. insert file OnDisk )
70
70
setFileModified ide True file
71
71
logDebug (ideLogger ide) $ " Saved text document: " <> getUri _uri
72
72
73
- , notificationHandler LSP. STextDocumentDidClose $
74
- \ ide (DidCloseTextDocumentParams TextDocumentIdentifier {_uri}) -> liftIO $ do
73
+ , mkPluginNotificationHandler LSP. STextDocumentDidClose $
74
+ \ ide _ (DidCloseTextDocumentParams TextDocumentIdentifier {_uri}) -> liftIO $ do
75
75
whenUriFile _uri $ \ file -> do
76
76
modifyFilesOfInterest ide (M. delete file)
77
77
-- Refresh all the files that depended on this
78
78
checkParents <- optCheckParents =<< getIdeOptionsIO (shakeExtras ide)
79
79
when (checkParents >= CheckOnClose ) $ typecheckParents ide file
80
80
logDebug (ideLogger ide) $ " Closed text document: " <> getUri _uri
81
81
82
- , notificationHandler LSP. SWorkspaceDidChangeWatchedFiles $
83
- \ ide (DidChangeWatchedFilesParams (List fileEvents)) -> liftIO $ do
82
+ , mkPluginNotificationHandler LSP. SWorkspaceDidChangeWatchedFiles $
83
+ \ ide _ (DidChangeWatchedFilesParams (List fileEvents)) -> liftIO $ do
84
84
-- See Note [File existence cache and LSP file watchers] which explains why we get these notifications and
85
85
-- what we do with them
86
86
let msg = Text. pack $ show fileEvents
@@ -89,22 +89,22 @@ setHandlersNotifications = mconcat
89
89
resetFileStore ide fileEvents
90
90
setSomethingModified ide
91
91
92
- , notificationHandler LSP. SWorkspaceDidChangeWorkspaceFolders $
93
- \ ide (DidChangeWorkspaceFoldersParams events) -> liftIO $ do
92
+ , mkPluginNotificationHandler LSP. SWorkspaceDidChangeWorkspaceFolders $
93
+ \ ide _ (DidChangeWorkspaceFoldersParams events) -> liftIO $ do
94
94
let add = S. union
95
95
substract = flip S. difference
96
96
modifyWorkspaceFolders ide
97
97
$ add (foldMap (S. singleton . parseWorkspaceFolder) (_added events))
98
98
. substract (foldMap (S. singleton . parseWorkspaceFolder) (_removed events))
99
99
100
- , notificationHandler LSP. SWorkspaceDidChangeConfiguration $
101
- \ ide (DidChangeConfigurationParams cfg) -> liftIO $ do
100
+ , mkPluginNotificationHandler LSP. SWorkspaceDidChangeConfiguration $
101
+ \ ide _ (DidChangeConfigurationParams cfg) -> liftIO $ do
102
102
let msg = Text. pack $ show cfg
103
103
logDebug (ideLogger ide) $ " Configuration changed: " <> msg
104
104
modifyClientSettings ide (const $ Just cfg)
105
105
setSomethingModified ide
106
106
107
- , notificationHandler LSP. SInitialized $ \ ide _ -> do
107
+ , mkPluginNotificationHandler LSP. SInitialized $ \ ide _ _ -> do
108
108
clientCapabilities <- LSP. getClientCapabilities
109
109
let watchSupported = case () of
110
110
_ | LSP. ClientCapabilities {_workspace} <- clientCapabilities
@@ -139,3 +139,4 @@ setHandlersNotifications = mconcat
139
139
void $ LSP. sendRequest SClientRegisterCapability regParams (const $ pure () ) -- TODO handle response
140
140
else liftIO $ logDebug (ideLogger ide) " Warning: Client does not support watched files. Falling back to OS polling"
141
141
]
142
+ }
0 commit comments