11{-# LANGUAGE OverloadedStrings #-}
22{-# LANGUAGE TypeOperators #-}
33{-# LANGUAGE FlexibleContexts #-}
4- {-# LANGUAGE KindSignatures #-}
54{-# LANGUAGE GADTs #-}
65{-# LANGUAGE RankNTypes #-}
76{-# LANGUAGE TypeInType #-}
@@ -119,7 +118,7 @@ import Data.List
119118import Data.Maybe
120119import Language.LSP.Types
121120import Language.LSP.Types.Lens hiding
122- (id , capabilities , message , executeCommand , applyEdit , rename )
121+ (id , capabilities , message , executeCommand , applyEdit , rename , to )
123122import qualified Language.LSP.Types.Lens as LSP
124123import qualified Language.LSP.Types.Capabilities as C
125124import Language.LSP.VFS
@@ -135,6 +134,7 @@ import System.Directory
135134import System.FilePath
136135import System.Process (ProcessHandle )
137136import qualified System.FilePath.Glob as Glob
137+ import Control.Monad.State (execState )
138138
139139-- | Starts a new session.
140140--
@@ -280,7 +280,7 @@ envOverrideConfig cfg = do
280280documentContents :: TextDocumentIdentifier -> Session T. Text
281281documentContents doc = do
282282 vfs <- vfs <$> get
283- let file = vfsMap vfs Map. ! toNormalizedUri (doc ^. uri)
283+ let Just file = vfs ^. vfsMap . at ( toNormalizedUri (doc ^. uri) )
284284 return (virtualFileText file)
285285
286286-- | Parses an ApplyEditRequest, checks that it is for the passed document
@@ -348,24 +348,24 @@ sendNotification :: SClientMethod (m :: Method FromClient Notification) -- ^ The
348348sendNotification STextDocumentDidOpen params = do
349349 let n = NotificationMessage " 2.0" STextDocumentDidOpen params
350350 oldVFS <- vfs <$> get
351- let ( newVFS,_) = openVFS oldVFS n
351+ let newVFS = flip execState oldVFS $ openVFS mempty n
352352 modify (\ s -> s { vfs = newVFS })
353353 sendMessage n
354354
355355-- Close a virtual file if we send a close text document notification
356356sendNotification STextDocumentDidClose params = do
357357 let n = NotificationMessage " 2.0" STextDocumentDidClose params
358358 oldVFS <- vfs <$> get
359- let ( newVFS,_) = closeVFS oldVFS n
359+ let newVFS = flip execState oldVFS $ closeVFS mempty n
360360 modify (\ s -> s { vfs = newVFS })
361361 sendMessage n
362362
363363sendNotification 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
369369
370370sendNotification method params =
371371 case splitClientMethod method of
@@ -594,11 +594,8 @@ executeCodeAction action = do
594594-- | Adds the current version to the document, as tracked by the session.
595595getVersionedDoc :: TextDocumentIdentifier -> Session VersionedTextDocumentIdentifier
596596getVersionedDoc (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
602599 return (VersionedTextDocumentIdentifier uri ver)
603600
604601-- | Applys an edit to the document and returns the updated document version.
0 commit comments