@@ -119,7 +119,7 @@ import Data.List
119
119
import Data.Maybe
120
120
import Language.LSP.Protocol.Types
121
121
import Language.LSP.Protocol.Message
122
- import qualified Language.LSP.Protocol.Lens as J
122
+ import qualified Language.LSP.Protocol.Lens as L
123
123
import qualified Language.LSP.Protocol.Capabilities as C
124
124
import Language.LSP.VFS
125
125
import Language.LSP.Test.Compat
@@ -227,7 +227,7 @@ runSessionWithHandles' serverProc serverIn serverOut config' caps rootDir sessio
227
227
-- collect them and then...
228
228
(inBetween, initRspMsg) <- manyTill_ anyMessage (responseForId SMethod_Initialize initReqId)
229
229
230
- case initRspMsg ^. J . result of
230
+ case initRspMsg ^. L . result of
231
231
Left error -> liftIO $ putStrLn (" Error while initializing: " ++ show error )
232
232
Right _ -> pure ()
233
233
@@ -291,7 +291,7 @@ envOverrideConfig cfg = do
291
291
documentContents :: TextDocumentIdentifier -> Session T. Text
292
292
documentContents doc = do
293
293
vfs <- vfs <$> get
294
- let Just file = vfs ^. vfsMap . at (toNormalizedUri (doc ^. J . uri))
294
+ let Just file = vfs ^. vfsMap . at (toNormalizedUri (doc ^. L . uri))
295
295
return (virtualFileText file)
296
296
297
297
-- | Parses an ApplyEditRequest, checks that it is for the passed document
@@ -306,14 +306,14 @@ getDocumentEdit doc = do
306
306
documentContents doc
307
307
where
308
308
checkDocumentChanges req =
309
- let changes = req ^. J . params . J . edit . J . documentChanges
309
+ let changes = req ^. L . params . L . edit . L . documentChanges
310
310
maybeDocs = fmap (fmap documentChangeUri) changes
311
311
in case maybeDocs of
312
- Just docs -> (doc ^. J . uri) `elem` docs
312
+ Just docs -> (doc ^. L . uri) `elem` docs
313
313
Nothing -> False
314
314
checkChanges req =
315
- let mMap = req ^. J . params . J . edit . J . changes
316
- in maybe False (Map. member (doc ^. J . uri)) mMap
315
+ let mMap = req ^. L . params . L . edit . L . changes
316
+ in maybe False (Map. member (doc ^. L . uri)) mMap
317
317
318
318
-- | Sends a request to the server and waits for its response.
319
319
-- Will skip any messages in between the request and the response
@@ -432,10 +432,10 @@ createDoc file languageId contents = do
432
432
createHits _ = False
433
433
434
434
regHits :: TRegistration Method_WorkspaceDidChangeWatchedFiles -> Bool
435
- regHits reg = foldl' (\ acc w -> acc || watchHits w) False (reg ^. J . registerOptions . _Just . J . watchers)
435
+ regHits reg = foldl' (\ acc w -> acc || watchHits w) False (reg ^. L . registerOptions . _Just . L . watchers)
436
436
437
437
clientCapsSupports =
438
- caps ^? J . workspace . _Just . J . didChangeWatchedFiles . _Just . J . dynamicRegistration . _Just
438
+ caps ^? L . workspace . _Just . L . didChangeWatchedFiles . _Just . L . dynamicRegistration . _Just
439
439
== Just True
440
440
shouldSend = clientCapsSupports && foldl' (\ acc r -> acc || regHits r) False regs
441
441
@@ -467,14 +467,14 @@ openDoc' file languageId contents = do
467
467
-- | Closes a text document and sends a textDocument/didOpen notification to the server.
468
468
closeDoc :: TextDocumentIdentifier -> Session ()
469
469
closeDoc docId = do
470
- let params = DidCloseTextDocumentParams (TextDocumentIdentifier (docId ^. J . uri))
470
+ let params = DidCloseTextDocumentParams (TextDocumentIdentifier (docId ^. L . uri))
471
471
sendNotification SMethod_TextDocumentDidClose params
472
472
473
473
-- | Changes a text document and sends a textDocument/didOpen notification to the server.
474
474
changeDoc :: TextDocumentIdentifier -> [TextDocumentContentChangeEvent ] -> Session ()
475
475
changeDoc docId changes = do
476
476
verDoc <- getVersionedDoc docId
477
- let params = DidChangeTextDocumentParams (verDoc & J . version +~ 1 ) changes
477
+ let params = DidChangeTextDocumentParams (verDoc & L . version +~ 1 ) changes
478
478
sendNotification SMethod_TextDocumentDidChange params
479
479
480
480
-- | Gets the Uri for the file corrected to the session directory.
@@ -488,7 +488,7 @@ getDocUri file = do
488
488
waitForDiagnostics :: Session [Diagnostic ]
489
489
waitForDiagnostics = do
490
490
diagsNot <- skipManyTill anyMessage (message SMethod_TextDocumentPublishDiagnostics )
491
- let diags = diagsNot ^. J . params . J . diagnostics
491
+ let diags = diagsNot ^. L . params . L . diagnostics
492
492
return diags
493
493
494
494
-- | The same as 'waitForDiagnostics', but will only match a specific
@@ -502,15 +502,15 @@ waitForDiagnosticsSource src = do
502
502
else return res
503
503
where
504
504
matches :: Diagnostic -> Bool
505
- matches d = d ^. J . source == Just (T. pack src)
505
+ matches d = d ^. L . source == Just (T. pack src)
506
506
507
507
-- | Expects a 'PublishDiagnosticsNotification' and throws an
508
508
-- 'UnexpectedDiagnostics' exception if there are any diagnostics
509
509
-- returned.
510
510
noDiagnostics :: Session ()
511
511
noDiagnostics = do
512
512
diagsNot <- message SMethod_TextDocumentPublishDiagnostics
513
- when (diagsNot ^. J . params . J . diagnostics /= [] ) $ liftIO $ throw UnexpectedDiagnostics
513
+ when (diagsNot ^. L . params . L . diagnostics /= [] ) $ liftIO $ throw UnexpectedDiagnostics
514
514
515
515
-- | Returns the symbols in a document.
516
516
getDocumentSymbols :: TextDocumentIdentifier -> Session (Either [SymbolInformation ] [DocumentSymbol ])
@@ -528,10 +528,10 @@ getCodeActions doc range = do
528
528
ctx <- getCodeActionContextInRange doc range
529
529
rsp <- request SMethod_TextDocumentCodeAction (CodeActionParams Nothing Nothing doc range ctx)
530
530
531
- case rsp ^. J . result of
531
+ case rsp ^. L . result of
532
532
Right (InL xs) -> return xs
533
533
Right (InR _) -> return []
534
- Left error -> throw (UnexpectedResponseError (SomeLspId $ fromJust $ rsp ^. J .id ) error )
534
+ Left error -> throw (UnexpectedResponseError (SomeLspId $ fromJust $ rsp ^. L .id ) error )
535
535
536
536
-- | Returns all the code actions in a document by
537
537
-- querying the code actions at each of the current
@@ -545,7 +545,7 @@ getAllCodeActions doc = do
545
545
where
546
546
go :: CodeActionContext -> [Command |? CodeAction ] -> Diagnostic -> Session [Command |? CodeAction ]
547
547
go ctx acc diag = do
548
- TResponseMessage _ rspLid res <- request SMethod_TextDocumentCodeAction (CodeActionParams Nothing Nothing doc (diag ^. J . range) ctx)
548
+ TResponseMessage _ rspLid res <- request SMethod_TextDocumentCodeAction (CodeActionParams Nothing Nothing doc (diag ^. L . range) ctx)
549
549
550
550
case res of
551
551
Left e -> throw (UnexpectedResponseError (SomeLspId $ fromJust rspLid) e)
@@ -580,7 +580,7 @@ getCodeActionContext doc = do
580
580
-- | Returns the current diagnostics that have been sent to the client.
581
581
-- Note that this does not wait for more to come in.
582
582
getCurrentDiagnostics :: TextDocumentIdentifier -> Session [Diagnostic ]
583
- getCurrentDiagnostics doc = fromMaybe [] . Map. lookup (toNormalizedUri $ doc ^. J . uri) . curDiagnostics <$> get
583
+ getCurrentDiagnostics doc = fromMaybe [] . Map. lookup (toNormalizedUri $ doc ^. L . uri) . curDiagnostics <$> get
584
584
585
585
-- | Returns the tokens of all progress sessions that have started but not yet ended.
586
586
getIncompleteProgressSessions :: Session (Set. Set ProgressToken )
@@ -589,8 +589,8 @@ getIncompleteProgressSessions = curProgressSessions <$> get
589
589
-- | Executes a command.
590
590
executeCommand :: Command -> Session ()
591
591
executeCommand cmd = do
592
- let args = decode $ encode $ fromJust $ cmd ^. J . arguments
593
- execParams = ExecuteCommandParams Nothing (cmd ^. J . command) args
592
+ let args = decode $ encode $ fromJust $ cmd ^. L . arguments
593
+ execParams = ExecuteCommandParams Nothing (cmd ^. L . command) args
594
594
void $ sendRequest SMethod_WorkspaceExecuteCommand execParams
595
595
596
596
-- | Executes a code action.
@@ -599,8 +599,8 @@ executeCommand cmd = do
599
599
-- be applied first.
600
600
executeCodeAction :: CodeAction -> Session ()
601
601
executeCodeAction action = do
602
- maybe (return () ) handleEdit $ action ^. J . edit
603
- maybe (return () ) executeCommand $ action ^. J . command
602
+ maybe (return () ) handleEdit $ action ^. L . edit
603
+ maybe (return () ) executeCommand $ action ^. L . command
604
604
605
605
where handleEdit :: WorkspaceEdit -> Session ()
606
606
handleEdit e =
@@ -625,14 +625,14 @@ applyEdit doc edit = do
625
625
626
626
caps <- asks sessionCapabilities
627
627
628
- let supportsDocChanges = fromMaybe False $ caps ^? J . workspace . _Just . J . workspaceEdit . _Just . J . documentChanges . _Just
628
+ let supportsDocChanges = fromMaybe False $ caps ^? L . workspace . _Just . L . workspaceEdit . _Just . L . documentChanges . _Just
629
629
630
630
let wEdit = if supportsDocChanges
631
631
then
632
632
let docEdit = TextDocumentEdit (review _versionedTextDocumentIdentifier verDoc) [InL edit]
633
633
in WorkspaceEdit Nothing (Just [InL docEdit]) Nothing
634
634
else
635
- let changes = Map. singleton (doc ^. J . uri) [edit]
635
+ let changes = Map. singleton (doc ^. L . uri) [edit]
636
636
in WorkspaceEdit (Just changes) Nothing Nothing
637
637
638
638
let req = TRequestMessage " " (IdInt 0 ) SMethod_WorkspaceApplyEdit (ApplyWorkspaceEditParams Nothing wEdit)
@@ -648,7 +648,7 @@ getCompletions doc pos = do
648
648
649
649
case getResponseResult rsp of
650
650
InL items -> return items
651
- InR (InL c) -> return $ c ^. J . items
651
+ InR (InL c) -> return $ c ^. L . items
652
652
InR (InR _) -> return []
653
653
654
654
-- | Returns the references for the position in the document.
@@ -721,9 +721,9 @@ getHighlights doc pos =
721
721
-- Returns the result if successful.
722
722
getResponseResult :: (ToJSON (ErrorData m )) => TResponseMessage m -> MessageResult m
723
723
getResponseResult rsp =
724
- case rsp ^. J . result of
724
+ case rsp ^. L . result of
725
725
Right x -> x
726
- Left err -> throw $ UnexpectedResponseError (SomeLspId $ fromJust $ rsp ^. J .id ) err
726
+ Left err -> throw $ UnexpectedResponseError (SomeLspId $ fromJust $ rsp ^. L .id ) err
727
727
728
728
-- | Applies formatting to the specified document.
729
729
formatDoc :: TextDocumentIdentifier -> FormattingOptions -> Session ()
@@ -741,7 +741,7 @@ formatRange doc opts range = do
741
741
742
742
applyTextEdits :: TextDocumentIdentifier -> [TextEdit ] -> Session ()
743
743
applyTextEdits doc edits =
744
- let wEdit = WorkspaceEdit (Just (Map. singleton (doc ^. J . uri) edits)) Nothing Nothing
744
+ let wEdit = WorkspaceEdit (Just (Map. singleton (doc ^. L . uri) edits)) Nothing Nothing
745
745
-- Send a dummy message to updateState so it can do bookkeeping
746
746
req = TRequestMessage " " (IdInt 0 ) SMethod_WorkspaceApplyEdit (ApplyWorkspaceEditParams Nothing wEdit)
747
747
in updateState (FromServerMess SMethod_WorkspaceApplyEdit req)
0 commit comments