1
1
{-# LANGUAGE OverloadedStrings #-}
2
2
{-# LANGUAGE TypeOperators #-}
3
3
{-# LANGUAGE FlexibleContexts #-}
4
- {-# LANGUAGE KindSignatures #-}
5
4
{-# LANGUAGE GADTs #-}
6
5
{-# LANGUAGE RankNTypes #-}
7
6
{-# LANGUAGE TypeInType #-}
@@ -119,7 +118,7 @@ import Data.List
119
118
import Data.Maybe
120
119
import Language.LSP.Types
121
120
import Language.LSP.Types.Lens hiding
122
- (id , capabilities , message , executeCommand , applyEdit , rename )
121
+ (id , capabilities , message , executeCommand , applyEdit , rename , to )
123
122
import qualified Language.LSP.Types.Lens as LSP
124
123
import qualified Language.LSP.Types.Capabilities as C
125
124
import Language.LSP.VFS
@@ -135,6 +134,7 @@ import System.Directory
135
134
import System.FilePath
136
135
import System.Process (ProcessHandle )
137
136
import qualified System.FilePath.Glob as Glob
137
+ import Control.Monad.State (execState )
138
138
139
139
-- | Starts a new session.
140
140
--
@@ -280,7 +280,7 @@ envOverrideConfig cfg = do
280
280
documentContents :: TextDocumentIdentifier -> Session T. Text
281
281
documentContents doc = do
282
282
vfs <- vfs <$> get
283
- let file = vfsMap vfs Map. ! toNormalizedUri (doc ^. uri)
283
+ let Just file = vfs ^. vfsMap . at ( toNormalizedUri (doc ^. uri) )
284
284
return (virtualFileText file)
285
285
286
286
-- | Parses an ApplyEditRequest, checks that it is for the passed document
@@ -348,24 +348,24 @@ sendNotification :: SClientMethod (m :: Method FromClient Notification) -- ^ The
348
348
sendNotification STextDocumentDidOpen params = do
349
349
let n = NotificationMessage " 2.0" STextDocumentDidOpen params
350
350
oldVFS <- vfs <$> get
351
- let ( newVFS,_) = openVFS oldVFS n
351
+ let newVFS = flip execState oldVFS $ openVFS mempty n
352
352
modify (\ s -> s { vfs = newVFS })
353
353
sendMessage n
354
354
355
355
-- Close a virtual file if we send a close text document notification
356
356
sendNotification STextDocumentDidClose params = do
357
357
let n = NotificationMessage " 2.0" STextDocumentDidClose params
358
358
oldVFS <- vfs <$> get
359
- let ( newVFS,_) = closeVFS oldVFS n
359
+ let newVFS = flip execState oldVFS $ closeVFS mempty n
360
360
modify (\ s -> s { vfs = newVFS })
361
361
sendMessage n
362
362
363
363
sendNotification STextDocumentDidChange params = do
364
- let n = NotificationMessage " 2.0" STextDocumentDidChange params
365
- oldVFS <- vfs <$> get
366
- let ( newVFS,_) = changeFromClientVFS oldVFS n
367
- modify (\ s -> s { vfs = newVFS })
368
- sendMessage n
364
+ let n = NotificationMessage " 2.0" STextDocumentDidChange params
365
+ oldVFS <- vfs <$> get
366
+ let newVFS = flip execState oldVFS $ changeFromClientVFS mempty n
367
+ modify (\ s -> s { vfs = newVFS })
368
+ sendMessage n
369
369
370
370
sendNotification method params =
371
371
case splitClientMethod method of
@@ -594,11 +594,8 @@ executeCodeAction action = do
594
594
-- | Adds the current version to the document, as tracked by the session.
595
595
getVersionedDoc :: TextDocumentIdentifier -> Session VersionedTextDocumentIdentifier
596
596
getVersionedDoc (TextDocumentIdentifier uri) = do
597
- fs <- vfsMap . vfs <$> get
598
- let ver =
599
- case fs Map. !? toNormalizedUri uri of
600
- Just vf -> Just (virtualFileVersion vf)
601
- _ -> Nothing
597
+ vfs <- vfs <$> get
598
+ let ver = vfs ^? vfsMap . ix (toNormalizedUri uri) . to virtualFileVersion
602
599
return (VersionedTextDocumentIdentifier uri ver)
603
600
604
601
-- | Applys an edit to the document and returns the updated document version.
0 commit comments