Skip to content

Commit b7632ea

Browse files
authored
Merge branch 'master' into mpj/log-initial-config
2 parents e32fc6c + fee511b commit b7632ea

File tree

6 files changed

+18
-22
lines changed

6 files changed

+18
-22
lines changed

lsp-test/src/Language/LSP/Test/Session.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -282,8 +282,8 @@ runSession' serverIn serverOut mServerProc serverHandler config caps rootDir exi
282282
mainThreadId <- myThreadId
283283

284284
let context = SessionContext serverIn absRootDir messageChan timeoutIdVar reqMap initRsp config caps
285-
initState vfs = SessionState 0 vfs mempty False Nothing mempty (lspConfig config) mempty (ignoreLogNotifications config) (ignoreConfigurationRequests config)
286-
runSession' ses = initVFS $ \vfs -> runSessionMonad context (initState vfs) ses
285+
initState = SessionState 0 emptyVFS mempty False Nothing mempty (lspConfig config) mempty (ignoreLogNotifications config) (ignoreConfigurationRequests config)
286+
runSession' = runSessionMonad context initState
287287

288288
errorHandler = throwTo mainThreadId :: SessionException -> IO ()
289289
serverListenerLauncher =
@@ -306,7 +306,7 @@ runSession' serverIn serverOut mServerProc serverHandler config caps rootDir exi
306306

307307
(result, _) <- bracket serverListenerLauncher
308308
serverAndListenerFinalizer
309-
(const $ initVFS $ \vfs -> runSessionMonad context (initState vfs) session)
309+
(const $ runSessionMonad context initState session)
310310
return result
311311

312312
updateStateC :: ConduitM FromServerMessage FromServerMessage (StateT SessionState (ReaderT SessionContext IO)) ()

lsp/ChangeLog.md

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,8 @@
33
## Unreleased
44

55
- Fix inference of server capabilities for newer methods (except notebook methods).
6+
- VFS no longer requires IO to initialize, functions that wrote to a temporary directory
7+
now take the directory as an argument.
68

79
## 2.2.0.0
810

lsp/lsp.cabal

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -72,7 +72,6 @@ library
7272
, row-types
7373
, sorted-list ^>=0.2.1
7474
, stm ^>=2.5
75-
, temporary
7675
, text
7776
, text-rope
7877
, transformers >=0.5.6 && <0.7

lsp/src/Language/LSP/Server/Control.hs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -142,8 +142,7 @@ runServerWith ioLogger logger clientIn clientOut serverDefinition = do
142142

143143
let sendMsg msg = atomically $ writeTChan cout $ J.toJSON msg
144144

145-
initVFS $ \vfs -> do
146-
ioLoop ioLogger logger clientIn serverDefinition vfs sendMsg
145+
ioLoop ioLogger logger clientIn serverDefinition emptyVFS sendMsg
147146

148147
return 1
149148

lsp/src/Language/LSP/Server/Core.hs

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -453,13 +453,13 @@ snapshotVirtualFiles :: LanguageContextEnv c -> STM VFS
453453
snapshotVirtualFiles env = vfsData <$> readTVar (resVFS $ resState env)
454454
{-# INLINE snapshotVirtualFiles #-}
455455

456-
{- | Dump the current text for a given VFS file to a temporary file,
457-
and return the path to the file.
456+
{- | Dump the current text for a given VFS file to a file
457+
in the given directory and return the path to the file.
458458
-}
459-
persistVirtualFile :: MonadLsp config m => LogAction m (WithSeverity VfsLog) -> NormalizedUri -> m (Maybe FilePath)
460-
persistVirtualFile logger uri = do
459+
persistVirtualFile :: MonadLsp config m => LogAction m (WithSeverity VfsLog) -> FilePath -> NormalizedUri -> m (Maybe FilePath)
460+
persistVirtualFile logger dir uri = do
461461
join $ stateState resVFS $ \vfs ->
462-
case persistFileVFS logger (vfsData vfs) uri of
462+
case persistFileVFS logger dir (vfsData vfs) uri of
463463
Nothing -> (return Nothing, vfs)
464464
Just (fn, write) ->
465465
let !revMap = case uriToFilePath (fromNormalizedUri uri) of

lsp/src/Language/LSP/VFS.hs

Lines changed: 7 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -26,7 +26,6 @@ files in the client workspace by operating on the "VFS" in "LspFuncs".
2626
module Language.LSP.VFS (
2727
VFS (..),
2828
vfsMap,
29-
vfsTempDir,
3029
VirtualFile (..),
3130
lsp_version,
3231
file_version,
@@ -36,7 +35,7 @@ module Language.LSP.VFS (
3635
VfsLog (..),
3736

3837
-- * Managing the VFS
39-
initVFS,
38+
emptyVFS,
4039
openVFS,
4140
changeFromClientVFS,
4241
changeFromServerVFS,
@@ -92,7 +91,6 @@ import Language.LSP.Protocol.Types qualified as J
9291
import System.Directory
9392
import System.FilePath
9493
import System.IO
95-
import System.IO.Temp
9694

9795
-- ---------------------------------------------------------------------
9896
{-# ANN module ("hlint: ignore Eta reduce" :: String) #-}
@@ -113,8 +111,6 @@ data VirtualFile = VirtualFile
113111

114112
data VFS = VFS
115113
{ _vfsMap :: !(Map.Map J.NormalizedUri VirtualFile)
116-
, _vfsTempDir :: !FilePath
117-
-- ^ This is where all the temporary files will be written to
118114
}
119115
deriving (Show)
120116

@@ -152,8 +148,8 @@ virtualFileVersion vf = _lsp_version vf
152148

153149
---
154150

155-
initVFS :: (VFS -> IO r) -> IO r
156-
initVFS k = withSystemTempDirectory "haskell-lsp" $ \temp_dir -> k (VFS mempty temp_dir)
151+
emptyVFS :: VFS
152+
emptyVFS = VFS mempty
157153

158154
-- ---------------------------------------------------------------------
159155

@@ -311,13 +307,13 @@ virtualFileName prefix uri (VirtualFile _ file_ver _) =
311307
in replicate (n - length numString) '0' ++ numString
312308
in prefix </> basename ++ "-" ++ padLeft 5 file_ver ++ "-" ++ show (hash uri_raw) <.> takeExtensions basename
313309

314-
-- | Write a virtual file to a temporary file if it exists in the VFS.
315-
persistFileVFS :: (MonadIO m) => LogAction m (WithSeverity VfsLog) -> VFS -> J.NormalizedUri -> Maybe (FilePath, m ())
316-
persistFileVFS logger vfs uri =
310+
-- | Write a virtual file to a file in the given directory if it exists in the VFS.
311+
persistFileVFS :: (MonadIO m) => LogAction m (WithSeverity VfsLog) -> FilePath -> VFS -> J.NormalizedUri -> Maybe (FilePath, m ())
312+
persistFileVFS logger dir vfs uri =
317313
case vfs ^. vfsMap . at uri of
318314
Nothing -> Nothing
319315
Just vf ->
320-
let tfn = virtualFileName (vfs ^. vfsTempDir) uri vf
316+
let tfn = virtualFileName dir uri vf
321317
action = do
322318
exists <- liftIO $ doesFileExist tfn
323319
unless exists $ do

0 commit comments

Comments
 (0)