@@ -20,7 +20,9 @@ module Development.IDE.Core.FileStore(
20
20
getModificationTimeImpl ,
21
21
addIdeGlobal ,
22
22
getFileContentsImpl ,
23
- getModTime
23
+ getModTime ,
24
+ isWatchSupported ,
25
+ registerFileWatches
24
26
) where
25
27
26
28
import Control.Concurrent.STM (atomically )
@@ -49,7 +51,8 @@ import Development.IDE.Types.Diagnostics
49
51
import Development.IDE.Types.Location
50
52
import Development.IDE.Types.Options
51
53
import HieDb.Create (deleteMissingRealFiles )
52
- import Ide.Plugin.Config (CheckParents (.. ))
54
+ import Ide.Plugin.Config (CheckParents (.. ),
55
+ Config )
53
56
import System.IO.Error
54
57
55
58
#ifdef mingw32_HOST_OS
@@ -63,13 +66,21 @@ import qualified Development.IDE.Types.Logger as L
63
66
64
67
import qualified Data.Binary as B
65
68
import qualified Data.ByteString.Lazy as LBS
69
+ import qualified Data.Text as Text
70
+ import Development.IDE.Core.IdeConfiguration (isWorkspaceFile )
66
71
import Language.LSP.Server hiding
67
72
(getVirtualFile )
68
73
import qualified Language.LSP.Server as LSP
69
- import Language.LSP.Types (FileChangeType (FcChanged ),
74
+ import Language.LSP.Types (DidChangeWatchedFilesRegistrationOptions (DidChangeWatchedFilesRegistrationOptions ),
75
+ FileChangeType (FcChanged ),
70
76
FileEvent (FileEvent ),
77
+ FileSystemWatcher (.. ),
78
+ WatchKind (.. ),
79
+ _watchers ,
71
80
toNormalizedFilePath ,
72
81
uriToFilePath )
82
+ import qualified Language.LSP.Types as LSP
83
+ import qualified Language.LSP.Types.Capabilities as LSP
73
84
import Language.LSP.VFS
74
85
import System.FilePath
75
86
@@ -94,6 +105,17 @@ makeLSPVFSHandle lspEnv = VFSHandle
94
105
, setVirtualFileContents = Nothing
95
106
}
96
107
108
+ addWatchedFileRule :: (NormalizedFilePath -> Action Bool ) -> Rules ()
109
+ addWatchedFileRule isWatched = defineNoDiagnostics $ \ AddWatchedFile f -> do
110
+ isAlreadyWatched <- isWatched f
111
+ isWp <- isWorkspaceFile f
112
+ if isAlreadyWatched then pure (Just True ) else
113
+ if not isWp then pure (Just False ) else do
114
+ ShakeExtras {lspEnv} <- getShakeExtras
115
+ case lspEnv of
116
+ Just env -> fmap Just $ liftIO $ LSP. runLspT env $
117
+ registerFileWatches [fromNormalizedFilePath f]
118
+ Nothing -> pure $ Just False
97
119
98
120
isFileOfInterestRule :: Rules ()
99
121
isFileOfInterestRule = defineEarlyCutoff $ RuleNoDiagnostics $ \ IsFileOfInterest f -> do
@@ -109,45 +131,44 @@ isFileOfInterestRule = defineEarlyCutoff $ RuleNoDiagnostics $ \IsFileOfInterest
109
131
summarize (IsFOI (Modified True )) = BS. singleton 3
110
132
111
133
112
- getModificationTimeRule :: VFSHandle -> ( NormalizedFilePath -> Action Bool ) -> Rules ()
113
- getModificationTimeRule vfs isWatched = defineEarlyCutoff $ Rule $ \ (GetModificationTime_ missingFileDiags) file ->
114
- getModificationTimeImpl vfs isWatched missingFileDiags file
134
+ getModificationTimeRule :: VFSHandle -> Rules ()
135
+ getModificationTimeRule vfs = defineEarlyCutoff $ Rule $ \ (GetModificationTime_ missingFileDiags) file ->
136
+ getModificationTimeImpl vfs missingFileDiags file
115
137
116
138
getModificationTimeImpl :: VFSHandle
117
- -> (NormalizedFilePath -> Action Bool )
118
139
-> Bool
119
140
-> NormalizedFilePath
120
141
-> Action
121
142
(Maybe BS. ByteString , ([FileDiagnostic ], Maybe FileVersion ))
122
- getModificationTimeImpl vfs isWatched missingFileDiags file = do
123
- let file' = fromNormalizedFilePath file
124
- let wrap time = (Just $ LBS. toStrict $ B. encode $ toRational time, ([] , Just $ ModificationTime time))
125
- mbVirtual <- liftIO $ getVirtualFile vfs $ filePathToUri' file
126
- case mbVirtual of
127
- Just (virtualFileVersion -> ver) -> do
128
- alwaysRerun
129
- pure (Just $ LBS. toStrict $ B. encode ver, ([] , Just $ VFSVersion ver))
130
- Nothing -> do
131
- isWF <- isWatched file
132
- if isWF
133
- then -- the file is watched so we can rely on FileWatched notifications,
134
- -- but also need a dependency on IsFileOfInterest to reinstall
135
- -- alwaysRerun when the file becomes VFS
136
- void (use_ IsFileOfInterest file)
137
- else if isInterface file
138
- then -- interface files are tracked specially using the closed world assumption
139
- pure ()
140
- else -- in all other cases we will need to freshly check the file system
141
- alwaysRerun
143
+ getModificationTimeImpl vfs missingFileDiags file = do
144
+ let file' = fromNormalizedFilePath file
145
+ let wrap time = (Just $ LBS. toStrict $ B. encode $ toRational time, ([] , Just $ ModificationTime time))
146
+ mbVirtual <- liftIO $ getVirtualFile vfs $ filePathToUri' file
147
+ case mbVirtual of
148
+ Just (virtualFileVersion -> ver) -> do
149
+ alwaysRerun
150
+ pure (Just $ LBS. toStrict $ B. encode ver, ([] , Just $ VFSVersion ver))
151
+ Nothing -> do
152
+ isWF <- use_ AddWatchedFile file
153
+ if isWF
154
+ then -- the file is watched so we can rely on FileWatched notifications,
155
+ -- but also need a dependency on IsFileOfInterest to reinstall
156
+ -- alwaysRerun when the file becomes VFS
157
+ void (use_ IsFileOfInterest file)
158
+ else if isInterface file
159
+ then -- interface files are tracked specially using the closed world assumption
160
+ pure ()
161
+ else -- in all other cases we will need to freshly check the file system
162
+ alwaysRerun
142
163
143
- liftIO $ fmap wrap (getModTime file')
144
- `catch` \ (e :: IOException ) -> do
145
- let err | isDoesNotExistError e = " File does not exist: " ++ file'
146
- | otherwise = " IO error while reading " ++ file' ++ " , " ++ displayException e
147
- diag = ideErrorText file (T. pack err)
148
- if isDoesNotExistError e && not missingFileDiags
149
- then return (Nothing , ([] , Nothing ))
150
- else return (Nothing , ([diag], Nothing ))
164
+ liftIO $ fmap wrap (getModTime file')
165
+ `catch` \ (e :: IOException ) -> do
166
+ let err | isDoesNotExistError e = " File does not exist: " ++ file'
167
+ | otherwise = " IO error while reading " ++ file' ++ " , " ++ displayException e
168
+ diag = ideErrorText file (T. pack err)
169
+ if isDoesNotExistError e && not missingFileDiags
170
+ then return (Nothing , ([] , Nothing ))
171
+ else return (Nothing , ([diag], Nothing ))
151
172
152
173
-- | Interface files cannot be watched, since they live outside the workspace.
153
174
-- But interface files are private, in that only HLS writes them.
@@ -239,9 +260,10 @@ getFileContents f = do
239
260
fileStoreRules :: VFSHandle -> (NormalizedFilePath -> Action Bool ) -> Rules ()
240
261
fileStoreRules vfs isWatched = do
241
262
addIdeGlobal vfs
242
- getModificationTimeRule vfs isWatched
263
+ getModificationTimeRule vfs
243
264
getFileContentsRule vfs
244
265
isFileOfInterestRule
266
+ addWatchedFileRule isWatched
245
267
246
268
-- | Note that some buffer for a specific file has been modified but not
247
269
-- with what changes.
@@ -290,3 +312,43 @@ setSomethingModified state = do
290
312
-- Update database to remove any files that might have been renamed/deleted
291
313
atomically $ writeTQueue (indexQueue $ hiedbWriter $ shakeExtras state) deleteMissingRealFiles
292
314
void $ shakeRestart state []
315
+
316
+ registerFileWatches :: [String ] -> LSP. LspT Config IO Bool
317
+ registerFileWatches globs = do
318
+ watchSupported <- isWatchSupported
319
+ if watchSupported
320
+ then do
321
+ let
322
+ regParams = LSP. RegistrationParams (List [LSP. SomeRegistration registration])
323
+ -- The registration ID is arbitrary and is only used in case we want to deregister (which we won't).
324
+ -- We could also use something like a random UUID, as some other servers do, but this works for
325
+ -- our purposes.
326
+ registration = LSP. Registration " globalFileWatches"
327
+ LSP. SWorkspaceDidChangeWatchedFiles
328
+ regOptions
329
+ regOptions =
330
+ DidChangeWatchedFilesRegistrationOptions { _watchers = List watchers }
331
+ -- See Note [File existence cache and LSP file watchers] for why this exists, and the choice of watch kind
332
+ watchKind = WatchKind { _watchCreate = True , _watchChange = True , _watchDelete = True }
333
+ -- See Note [Which files should we watch?] for an explanation of why the pattern is the way that it is
334
+ -- The patterns will be something like "**/.hs", i.e. "any number of directory segments,
335
+ -- followed by a file with an extension 'hs'.
336
+ watcher glob = FileSystemWatcher { _globPattern = glob, _kind = Just watchKind }
337
+ -- We use multiple watchers instead of one using '{}' because lsp-test doesn't
338
+ -- support that: https://github.com/bubba/lsp-test/issues/77
339
+ watchers = [ watcher (Text. pack glob) | glob <- globs ]
340
+
341
+ void $ LSP. sendRequest LSP. SClientRegisterCapability regParams (const $ pure () )
342
+ return True
343
+ else return False
344
+
345
+ isWatchSupported :: LSP. LspT Config IO Bool
346
+ isWatchSupported = do
347
+ clientCapabilities <- LSP. getClientCapabilities
348
+ pure $ case () of
349
+ _ | LSP. ClientCapabilities {_workspace} <- clientCapabilities
350
+ , Just LSP. WorkspaceClientCapabilities {_didChangeWatchedFiles} <- _workspace
351
+ , Just LSP. DidChangeWatchedFilesClientCapabilities {_dynamicRegistration} <- _didChangeWatchedFiles
352
+ , Just True <- _dynamicRegistration
353
+ -> True
354
+ | otherwise -> False
0 commit comments