5
5
6
6
module Development.IDE.Core.FileStore (
7
7
getFileContents ,
8
- getVirtualFile ,
9
8
setFileModified ,
10
9
setSomethingModified ,
11
10
fileStoreRules ,
12
11
modificationTime ,
13
12
typecheckParents ,
14
- VFSHandle ,
15
- makeVFSHandle ,
16
- makeLSPVFSHandle ,
17
13
resetFileStore ,
18
14
resetInterfaceStore ,
19
15
getModificationTimeImpl ,
@@ -28,20 +24,18 @@ module Development.IDE.Core.FileStore(
28
24
import Control.Concurrent.STM.Stats (STM , atomically ,
29
25
modifyTVar' )
30
26
import Control.Concurrent.STM.TQueue (writeTQueue )
31
- import Control.Concurrent.Strict
32
27
import Control.Exception
33
28
import Control.Monad.Extra
34
29
import Control.Monad.IO.Class
35
30
import qualified Data.ByteString as BS
36
31
import Data.Either.Extra
37
- import qualified Data.Map.Strict as Map
38
- import Data.Maybe
39
32
import qualified Data.Rope.UTF16 as Rope
40
33
import qualified Data.Text as T
41
34
import Data.Time
42
35
import Data.Time.Clock.POSIX
43
36
import Development.IDE.Core.RuleTypes
44
37
import Development.IDE.Core.Shake hiding (Log )
38
+ import Development.IDE.Core.FileUtils
45
39
import Development.IDE.GHC.Orphans ()
46
40
import Development.IDE.Graph
47
41
import Development.IDE.Import.DependencyInformation
@@ -56,8 +50,6 @@ import System.IO.Error
56
50
#ifdef mingw32_HOST_OS
57
51
import qualified System.Directory as Dir
58
52
#else
59
- import System.Posix.Files (getFileStatus ,
60
- modificationTimeHiRes )
61
53
#endif
62
54
63
55
import qualified Development.IDE.Types.Logger as L
@@ -76,8 +68,6 @@ import Development.IDE.Types.Logger (Pretty (pretty),
76
68
cmapWithPrio ,
77
69
logWith , viaShow ,
78
70
(<+>) )
79
- import Language.LSP.Server hiding
80
- (getVirtualFile )
81
71
import qualified Language.LSP.Server as LSP
82
72
import Language.LSP.Types (DidChangeWatchedFilesRegistrationOptions (DidChangeWatchedFilesRegistrationOptions ),
83
73
FileChangeType (FcChanged ),
@@ -106,27 +96,6 @@ instance Pretty Log where
106
96
<+> pretty (fmap (fmap show ) reverseDepPaths)
107
97
LogShake log -> pretty log
108
98
109
- makeVFSHandle :: IO VFSHandle
110
- makeVFSHandle = do
111
- vfsVar <- newVar (1 , Map. empty)
112
- pure VFSHandle
113
- { getVirtualFile = \ uri -> do
114
- (_nextVersion, vfs) <- readVar vfsVar
115
- pure $ Map. lookup uri vfs
116
- , setVirtualFileContents = Just $ \ uri content ->
117
- void $ modifyVar' vfsVar $ \ (nextVersion, vfs) -> (nextVersion + 1 , ) $
118
- case content of
119
- Nothing -> Map. delete uri vfs
120
- -- The second version number is only used in persistFileVFS which we do not use so we set it to 0.
121
- Just content -> Map. insert uri (VirtualFile nextVersion 0 (Rope. fromText content)) vfs
122
- }
123
-
124
- makeLSPVFSHandle :: LanguageContextEnv c -> VFSHandle
125
- makeLSPVFSHandle lspEnv = VFSHandle
126
- { getVirtualFile = runLspT lspEnv . LSP. getVirtualFile
127
- , setVirtualFileContents = Nothing
128
- }
129
-
130
99
addWatchedFileRule :: Recorder (WithPriority Log ) -> (NormalizedFilePath -> Action Bool ) -> Rules ()
131
100
addWatchedFileRule recorder isWatched = defineNoDiagnostics (cmapWithPrio LogShake recorder) $ \ AddWatchedFile f -> do
132
101
isAlreadyWatched <- isWatched f
@@ -140,20 +109,19 @@ addWatchedFileRule recorder isWatched = defineNoDiagnostics (cmapWithPrio LogSha
140
109
Nothing -> pure $ Just False
141
110
142
111
143
- getModificationTimeRule :: Recorder (WithPriority Log ) -> VFSHandle -> Rules ()
144
- getModificationTimeRule recorder vfs = defineEarlyCutoff (cmapWithPrio LogShake recorder) $ Rule $ \ (GetModificationTime_ missingFileDiags) file ->
145
- getModificationTimeImpl vfs missingFileDiags file
112
+ getModificationTimeRule :: Recorder (WithPriority Log ) -> Rules ()
113
+ getModificationTimeRule recorder = defineEarlyCutoff (cmapWithPrio LogShake recorder) $ Rule $ \ (GetModificationTime_ missingFileDiags) file ->
114
+ getModificationTimeImpl missingFileDiags file
146
115
147
- getModificationTimeImpl :: VFSHandle
148
- -> Bool
149
- -> NormalizedFilePath
150
- -> Action
151
- (Maybe BS. ByteString , ([FileDiagnostic ], Maybe FileVersion ))
152
- getModificationTimeImpl vfs missingFileDiags file = do
116
+ getModificationTimeImpl
117
+ :: Bool
118
+ -> NormalizedFilePath
119
+ -> Action (Maybe BS. ByteString , ([FileDiagnostic ], Maybe FileVersion ))
120
+ getModificationTimeImpl missingFileDiags file = do
153
121
let file' = fromNormalizedFilePath file
154
122
let wrap time = (Just $ LBS. toStrict $ B. encode $ toRational time, ([] , Just $ ModificationTime time))
155
- mbVirtual <- liftIO $ getVirtualFile vfs $ filePathToUri' file
156
- case mbVirtual of
123
+ mbVf <- getVirtualFile file
124
+ case mbVf of
157
125
Just (virtualFileVersion -> ver) -> do
158
126
alwaysRerun
159
127
pure (Just $ LBS. toStrict $ B. encode ver, ([] , Just $ VFSVersion ver))
@@ -206,43 +174,23 @@ resetFileStore ideState changes = mask $ \_ -> do
206
174
_ -> pure ()
207
175
208
176
209
- -- Dir.getModificationTime is surprisingly slow since it performs
210
- -- a ton of conversions. Since we do not actually care about
211
- -- the format of the time, we can get away with something cheaper.
212
- -- For now, we only try to do this on Unix systems where it seems to get the
213
- -- time spent checking file modifications (which happens on every change)
214
- -- from > 0.5s to ~0.15s.
215
- -- We might also want to try speeding this up on Windows at some point.
216
- -- TODO leverage DidChangeWatchedFile lsp notifications on clients that
217
- -- support them, as done for GetFileExists
218
- getModTime :: FilePath -> IO POSIXTime
219
- getModTime f =
220
- #ifdef mingw32_HOST_OS
221
- utcTimeToPOSIXSeconds <$> Dir. getModificationTime f
222
- #else
223
- modificationTimeHiRes <$> getFileStatus f
224
- #endif
225
-
226
177
modificationTime :: FileVersion -> Maybe UTCTime
227
178
modificationTime VFSVersion {} = Nothing
228
179
modificationTime (ModificationTime posix) = Just $ posixSecondsToUTCTime posix
229
180
230
- getFileContentsRule :: Recorder (WithPriority Log ) -> VFSHandle -> Rules ()
231
- getFileContentsRule recorder vfs = define (cmapWithPrio LogShake recorder) $ \ GetFileContents file -> getFileContentsImpl vfs file
181
+ getFileContentsRule :: Recorder (WithPriority Log ) -> Rules ()
182
+ getFileContentsRule recorder = define (cmapWithPrio LogShake recorder) $ \ GetFileContents file -> getFileContentsImpl file
232
183
233
184
getFileContentsImpl
234
- :: VFSHandle
235
- -> NormalizedFilePath
185
+ :: NormalizedFilePath
236
186
-> Action ([FileDiagnostic ], Maybe (FileVersion , Maybe T. Text ))
237
- getFileContentsImpl vfs file = do
187
+ getFileContentsImpl file = do
238
188
-- need to depend on modification time to introduce a dependency with Cutoff
239
189
time <- use_ GetModificationTime file
240
- res <- liftIO $ ideTryIOException file $ do
241
- mbVirtual <- getVirtualFile vfs $ filePathToUri' file
190
+ res <- do
191
+ mbVirtual <- getVirtualFile file
242
192
pure $ Rope. toText . _text <$> mbVirtual
243
- case res of
244
- Left err -> return ([err], Nothing )
245
- Right contents -> return ([] , Just (time, contents))
193
+ pure ([] , Just (time, res))
246
194
247
195
ideTryIOException :: NormalizedFilePath -> IO a -> IO (Either FileDiagnostic a )
248
196
ideTryIOException fp act =
@@ -266,11 +214,10 @@ getFileContents f = do
266
214
pure $ posixSecondsToUTCTime posix
267
215
return (modTime, txt)
268
216
269
- fileStoreRules :: Recorder (WithPriority Log ) -> VFSHandle -> (NormalizedFilePath -> Action Bool ) -> Rules ()
270
- fileStoreRules recorder vfs isWatched = do
271
- addIdeGlobal vfs
272
- getModificationTimeRule recorder vfs
273
- getFileContentsRule recorder vfs
217
+ fileStoreRules :: Recorder (WithPriority Log ) -> (NormalizedFilePath -> Action Bool ) -> Rules ()
218
+ fileStoreRules recorder isWatched = do
219
+ getModificationTimeRule recorder
220
+ getFileContentsRule recorder
274
221
addWatchedFileRule recorder isWatched
275
222
276
223
-- | Note that some buffer for a specific file has been modified but not
@@ -287,9 +234,6 @@ setFileModified recorder state saved nfp = do
287
234
AlwaysCheck -> True
288
235
CheckOnSave -> saved
289
236
_ -> False
290
- VFSHandle {.. } <- getIdeGlobalState state
291
- when (isJust setVirtualFileContents) $
292
- fail " setFileModified can't be called on this type of VFSHandle"
293
237
join $ atomically $ recordDirtyKeys (shakeExtras state) GetModificationTime [nfp]
294
238
restartShakeSession (shakeExtras state) (fromNormalizedFilePath nfp ++ " (modified)" ) []
295
239
when checkParents $
@@ -314,9 +258,6 @@ typecheckParentsAction recorder nfp = do
314
258
-- independently tracks which files are modified.
315
259
setSomethingModified :: IdeState -> [Key ] -> String -> IO ()
316
260
setSomethingModified state keys reason = do
317
- VFSHandle {.. } <- getIdeGlobalState state
318
- when (isJust setVirtualFileContents) $
319
- fail " setSomethingModified can't be called on this type of VFSHandle"
320
261
-- Update database to remove any files that might have been renamed/deleted
321
262
atomically $ do
322
263
writeTQueue (indexQueue $ hiedbWriter $ shakeExtras state) (\ withHieDb -> withHieDb deleteMissingRealFiles)
0 commit comments