Skip to content

Commit 06b09d0

Browse files
committed
Qualify lens classes as L instead of J
1 parent 96ae6f0 commit 06b09d0

File tree

7 files changed

+126
-126
lines changed

7 files changed

+126
-126
lines changed

lsp-test/func-test/FuncTest.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,7 @@ module Main where
55
import Language.LSP.Server
66
import qualified Language.LSP.Test as Test
77
import Language.LSP.Protocol.Types
8-
import qualified Language.LSP.Protocol.Lens as J
8+
import qualified Language.LSP.Protocol.Lens as L
99
import Language.LSP.Protocol.Message
1010
import Control.Monad.IO.Class
1111
import System.IO
@@ -57,15 +57,15 @@ main = hspec $ do
5757
-- First make sure that we get a $/progress begin notification
5858
skipManyTill Test.anyMessage $ do
5959
x <- Test.message SMethod_Progress
60-
guard $ has (J.params . J.value . _workDoneProgressBegin) x
60+
guard $ has (L.params . L.value . _workDoneProgressBegin) x
6161

6262
-- Then kill the thread
6363
liftIO $ putMVar killVar ()
6464

6565
-- Then make sure we still get a $/progress end notification
6666
skipManyTill Test.anyMessage $ do
6767
x <- Test.message SMethod_Progress
68-
guard $ has (J.params . J.value . _workDoneProgressEnd) x
68+
guard $ has (L.params . L.value . _workDoneProgressEnd) x
6969

7070
describe "workspace folders" $
7171
it "keeps track of open workspace folders" $ do

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

Lines changed: 28 additions & 28 deletions
Original file line numberDiff line numberDiff line change
@@ -119,7 +119,7 @@ import Data.List
119119
import Data.Maybe
120120
import Language.LSP.Protocol.Types
121121
import Language.LSP.Protocol.Message
122-
import qualified Language.LSP.Protocol.Lens as J
122+
import qualified Language.LSP.Protocol.Lens as L
123123
import qualified Language.LSP.Protocol.Capabilities as C
124124
import Language.LSP.VFS
125125
import Language.LSP.Test.Compat
@@ -227,7 +227,7 @@ runSessionWithHandles' serverProc serverIn serverOut config' caps rootDir sessio
227227
-- collect them and then...
228228
(inBetween, initRspMsg) <- manyTill_ anyMessage (responseForId SMethod_Initialize initReqId)
229229

230-
case initRspMsg ^. J.result of
230+
case initRspMsg ^. L.result of
231231
Left error -> liftIO $ putStrLn ("Error while initializing: " ++ show error)
232232
Right _ -> pure ()
233233

@@ -291,7 +291,7 @@ envOverrideConfig cfg = do
291291
documentContents :: TextDocumentIdentifier -> Session T.Text
292292
documentContents doc = do
293293
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))
295295
return (virtualFileText file)
296296

297297
-- | Parses an ApplyEditRequest, checks that it is for the passed document
@@ -306,14 +306,14 @@ getDocumentEdit doc = do
306306
documentContents doc
307307
where
308308
checkDocumentChanges req =
309-
let changes = req ^. J.params . J.edit . J.documentChanges
309+
let changes = req ^. L.params . L.edit . L.documentChanges
310310
maybeDocs = fmap (fmap documentChangeUri) changes
311311
in case maybeDocs of
312-
Just docs -> (doc ^. J.uri) `elem` docs
312+
Just docs -> (doc ^. L.uri) `elem` docs
313313
Nothing -> False
314314
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
317317

318318
-- | Sends a request to the server and waits for its response.
319319
-- Will skip any messages in between the request and the response
@@ -432,10 +432,10 @@ createDoc file languageId contents = do
432432
createHits _ = False
433433

434434
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)
436436

437437
clientCapsSupports =
438-
caps ^? J.workspace . _Just . J.didChangeWatchedFiles . _Just . J.dynamicRegistration . _Just
438+
caps ^? L.workspace . _Just . L.didChangeWatchedFiles . _Just . L.dynamicRegistration . _Just
439439
== Just True
440440
shouldSend = clientCapsSupports && foldl' (\acc r -> acc || regHits r) False regs
441441

@@ -467,14 +467,14 @@ openDoc' file languageId contents = do
467467
-- | Closes a text document and sends a textDocument/didOpen notification to the server.
468468
closeDoc :: TextDocumentIdentifier -> Session ()
469469
closeDoc docId = do
470-
let params = DidCloseTextDocumentParams (TextDocumentIdentifier (docId ^. J.uri))
470+
let params = DidCloseTextDocumentParams (TextDocumentIdentifier (docId ^. L.uri))
471471
sendNotification SMethod_TextDocumentDidClose params
472472

473473
-- | Changes a text document and sends a textDocument/didOpen notification to the server.
474474
changeDoc :: TextDocumentIdentifier -> [TextDocumentContentChangeEvent] -> Session ()
475475
changeDoc docId changes = do
476476
verDoc <- getVersionedDoc docId
477-
let params = DidChangeTextDocumentParams (verDoc & J.version +~ 1) changes
477+
let params = DidChangeTextDocumentParams (verDoc & L.version +~ 1) changes
478478
sendNotification SMethod_TextDocumentDidChange params
479479

480480
-- | Gets the Uri for the file corrected to the session directory.
@@ -488,7 +488,7 @@ getDocUri file = do
488488
waitForDiagnostics :: Session [Diagnostic]
489489
waitForDiagnostics = do
490490
diagsNot <- skipManyTill anyMessage (message SMethod_TextDocumentPublishDiagnostics)
491-
let diags = diagsNot ^. J.params . J.diagnostics
491+
let diags = diagsNot ^. L.params . L.diagnostics
492492
return diags
493493

494494
-- | The same as 'waitForDiagnostics', but will only match a specific
@@ -502,15 +502,15 @@ waitForDiagnosticsSource src = do
502502
else return res
503503
where
504504
matches :: Diagnostic -> Bool
505-
matches d = d ^. J.source == Just (T.pack src)
505+
matches d = d ^. L.source == Just (T.pack src)
506506

507507
-- | Expects a 'PublishDiagnosticsNotification' and throws an
508508
-- 'UnexpectedDiagnostics' exception if there are any diagnostics
509509
-- returned.
510510
noDiagnostics :: Session ()
511511
noDiagnostics = do
512512
diagsNot <- message SMethod_TextDocumentPublishDiagnostics
513-
when (diagsNot ^. J.params . J.diagnostics /= []) $ liftIO $ throw UnexpectedDiagnostics
513+
when (diagsNot ^. L.params . L.diagnostics /= []) $ liftIO $ throw UnexpectedDiagnostics
514514

515515
-- | Returns the symbols in a document.
516516
getDocumentSymbols :: TextDocumentIdentifier -> Session (Either [SymbolInformation] [DocumentSymbol])
@@ -528,10 +528,10 @@ getCodeActions doc range = do
528528
ctx <- getCodeActionContextInRange doc range
529529
rsp <- request SMethod_TextDocumentCodeAction (CodeActionParams Nothing Nothing doc range ctx)
530530

531-
case rsp ^. J.result of
531+
case rsp ^. L.result of
532532
Right (InL xs) -> return xs
533533
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)
535535

536536
-- | Returns all the code actions in a document by
537537
-- querying the code actions at each of the current
@@ -545,7 +545,7 @@ getAllCodeActions doc = do
545545
where
546546
go :: CodeActionContext -> [Command |? CodeAction] -> Diagnostic -> Session [Command |? CodeAction]
547547
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)
549549

550550
case res of
551551
Left e -> throw (UnexpectedResponseError (SomeLspId $ fromJust rspLid) e)
@@ -580,7 +580,7 @@ getCodeActionContext doc = do
580580
-- | Returns the current diagnostics that have been sent to the client.
581581
-- Note that this does not wait for more to come in.
582582
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
584584

585585
-- | Returns the tokens of all progress sessions that have started but not yet ended.
586586
getIncompleteProgressSessions :: Session (Set.Set ProgressToken)
@@ -589,8 +589,8 @@ getIncompleteProgressSessions = curProgressSessions <$> get
589589
-- | Executes a command.
590590
executeCommand :: Command -> Session ()
591591
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
594594
void $ sendRequest SMethod_WorkspaceExecuteCommand execParams
595595

596596
-- | Executes a code action.
@@ -599,8 +599,8 @@ executeCommand cmd = do
599599
-- be applied first.
600600
executeCodeAction :: CodeAction -> Session ()
601601
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
604604

605605
where handleEdit :: WorkspaceEdit -> Session ()
606606
handleEdit e =
@@ -625,14 +625,14 @@ applyEdit doc edit = do
625625

626626
caps <- asks sessionCapabilities
627627

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
629629

630630
let wEdit = if supportsDocChanges
631631
then
632632
let docEdit = TextDocumentEdit (review _versionedTextDocumentIdentifier verDoc) [InL edit]
633633
in WorkspaceEdit Nothing (Just [InL docEdit]) Nothing
634634
else
635-
let changes = Map.singleton (doc ^. J.uri) [edit]
635+
let changes = Map.singleton (doc ^. L.uri) [edit]
636636
in WorkspaceEdit (Just changes) Nothing Nothing
637637

638638
let req = TRequestMessage "" (IdInt 0) SMethod_WorkspaceApplyEdit (ApplyWorkspaceEditParams Nothing wEdit)
@@ -648,7 +648,7 @@ getCompletions doc pos = do
648648

649649
case getResponseResult rsp of
650650
InL items -> return items
651-
InR (InL c) -> return $ c ^. J.items
651+
InR (InL c) -> return $ c ^. L.items
652652
InR (InR _) -> return []
653653

654654
-- | Returns the references for the position in the document.
@@ -721,9 +721,9 @@ getHighlights doc pos =
721721
-- Returns the result if successful.
722722
getResponseResult :: (ToJSON (ErrorData m)) => TResponseMessage m -> MessageResult m
723723
getResponseResult rsp =
724-
case rsp ^. J.result of
724+
case rsp ^. L.result of
725725
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
727727

728728
-- | Applies formatting to the specified document.
729729
formatDoc :: TextDocumentIdentifier -> FormattingOptions -> Session ()
@@ -741,7 +741,7 @@ formatRange doc opts range = do
741741

742742
applyTextEdits :: TextDocumentIdentifier -> [TextEdit] -> Session ()
743743
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
745745
-- Send a dummy message to updateState so it can do bookkeeping
746746
req = TRequestMessage "" (IdInt 0) SMethod_WorkspaceApplyEdit (ApplyWorkspaceEditParams Nothing wEdit)
747747
in updateState (FromServerMess SMethod_WorkspaceApplyEdit req)

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

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -16,7 +16,7 @@ import Data.Maybe
1616
import System.IO
1717
import System.IO.Error
1818
import Language.LSP.Protocol.Message
19-
import qualified Language.LSP.Protocol.Lens as J
19+
import qualified Language.LSP.Protocol.Lens as L
2020
import Language.LSP.Test.Exceptions
2121

2222
import Data.IxMap
@@ -64,10 +64,10 @@ getRequestMap = foldl' helper emptyIxMap
6464
helper acc msg = case msg of
6565
FromClientMess m mess -> case splitClientMethod m of
6666
IsClientNot -> acc
67-
IsClientReq -> fromJust $ updateRequestMap acc (mess ^. J.id) m
67+
IsClientReq -> fromJust $ updateRequestMap acc (mess ^. L.id) m
6868
IsClientEither -> case mess of
6969
NotMess _ -> acc
70-
ReqMess msg -> fromJust $ updateRequestMap acc (msg ^. J.id) m
70+
ReqMess msg -> fromJust $ updateRequestMap acc (msg ^. L.id) m
7171
_ -> acc
7272

7373
decodeFromServerMsg :: RequestMap -> B.ByteString -> (RequestMap, FromServerMessage)

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

Lines changed: 24 additions & 24 deletions
Original file line numberDiff line numberDiff line change
@@ -12,7 +12,7 @@ where
1212

1313
import Language.LSP.Protocol.Message
1414
import Language.LSP.Protocol.Types
15-
import qualified Language.LSP.Protocol.Lens as J
15+
import qualified Language.LSP.Protocol.Lens as L
1616
import Control.Lens
1717
import qualified Data.Map.Strict as M
1818
import qualified Data.Text as T
@@ -41,7 +41,7 @@ swapFiles relCurBaseDir msgs = do
4141
rootDir :: [Event] -> FilePath
4242
rootDir (ClientEv _ (FromClientMess SMethod_Initialize req):_) =
4343
fromMaybe (error "Couldn't find root dir") $ do
44-
rootUri <- case req ^. J.params . J.rootUri of
44+
rootUri <- case req ^. L.params . L.rootUri of
4545
InL r -> Just r
4646
InR _ -> error "Couldn't find root dir"
4747
uriToFilePath rootUri
@@ -55,46 +55,46 @@ mapUris f event =
5555

5656
where
5757
--TODO: Handle all other URIs that might need swapped
58-
fromClientMsg (FromClientMess m@SMethod_Initialize r) = FromClientMess m $ J.params .~ transformInit (r ^. J.params) $ r
59-
fromClientMsg (FromClientMess m@SMethod_TextDocumentDidOpen n) = FromClientMess m $ swapUri (J.params . J.textDocument) n
60-
fromClientMsg (FromClientMess m@SMethod_TextDocumentDidChange n) = FromClientMess m $ swapUri (J.params . J.textDocument) n
61-
fromClientMsg (FromClientMess m@SMethod_TextDocumentWillSave n) = FromClientMess m $ swapUri (J.params . J.textDocument) n
62-
fromClientMsg (FromClientMess m@SMethod_TextDocumentDidSave n) = FromClientMess m $ swapUri (J.params . J.textDocument) n
63-
fromClientMsg (FromClientMess m@SMethod_TextDocumentDidClose n) = FromClientMess m $ swapUri (J.params . J.textDocument) n
64-
fromClientMsg (FromClientMess m@SMethod_TextDocumentDocumentSymbol n) = FromClientMess m $ swapUri (J.params . J.textDocument) n
65-
fromClientMsg (FromClientMess m@SMethod_TextDocumentRename n) = FromClientMess m $ swapUri (J.params . J.textDocument) n
58+
fromClientMsg (FromClientMess m@SMethod_Initialize r) = FromClientMess m $ L.params .~ transformInit (r ^. L.params) $ r
59+
fromClientMsg (FromClientMess m@SMethod_TextDocumentDidOpen n) = FromClientMess m $ swapUri (L.params . L.textDocument) n
60+
fromClientMsg (FromClientMess m@SMethod_TextDocumentDidChange n) = FromClientMess m $ swapUri (L.params . L.textDocument) n
61+
fromClientMsg (FromClientMess m@SMethod_TextDocumentWillSave n) = FromClientMess m $ swapUri (L.params . L.textDocument) n
62+
fromClientMsg (FromClientMess m@SMethod_TextDocumentDidSave n) = FromClientMess m $ swapUri (L.params . L.textDocument) n
63+
fromClientMsg (FromClientMess m@SMethod_TextDocumentDidClose n) = FromClientMess m $ swapUri (L.params . L.textDocument) n
64+
fromClientMsg (FromClientMess m@SMethod_TextDocumentDocumentSymbol n) = FromClientMess m $ swapUri (L.params . L.textDocument) n
65+
fromClientMsg (FromClientMess m@SMethod_TextDocumentRename n) = FromClientMess m $ swapUri (L.params . L.textDocument) n
6666
fromClientMsg x = x
6767

6868
fromServerMsg :: FromServerMessage -> FromServerMessage
69-
fromServerMsg (FromServerMess m@SMethod_WorkspaceApplyEdit r) = FromServerMess m $ J.params . J.edit .~ swapWorkspaceEdit (r ^. J.params . J.edit) $ r
70-
fromServerMsg (FromServerMess m@SMethod_TextDocumentPublishDiagnostics n) = FromServerMess m $ swapUri J.params n
69+
fromServerMsg (FromServerMess m@SMethod_WorkspaceApplyEdit r) = FromServerMess m $ L.params . L.edit .~ swapWorkspaceEdit (r ^. L.params . L.edit) $ r
70+
fromServerMsg (FromServerMess m@SMethod_TextDocumentPublishDiagnostics n) = FromServerMess m $ swapUri L.params n
7171
fromServerMsg (FromServerRsp m@SMethod_TextDocumentDocumentSymbol r) =
7272
let swapUri' :: ([SymbolInformation] |? [DocumentSymbol] |? Null) -> [SymbolInformation] |? [DocumentSymbol] |? Null
7373
swapUri' (InR (InL dss)) = InR $ InL dss -- no file locations here
7474
swapUri' (InR (InR n)) = InR $ InR n
75-
swapUri' (InL si) = InL (swapUri J.location <$> si)
76-
in FromServerRsp m $ r & J.result . _Right %~ swapUri'
77-
fromServerMsg (FromServerRsp m@SMethod_TextDocumentRename r) = FromServerRsp m $ r & J.result . _Right . _L %~ swapWorkspaceEdit
75+
swapUri' (InL si) = InL (swapUri L.location <$> si)
76+
in FromServerRsp m $ r & L.result . _Right %~ swapUri'
77+
fromServerMsg (FromServerRsp m@SMethod_TextDocumentRename r) = FromServerRsp m $ r & L.result . _Right . _L %~ swapWorkspaceEdit
7878
fromServerMsg x = x
7979

8080
swapWorkspaceEdit :: WorkspaceEdit -> WorkspaceEdit
8181
swapWorkspaceEdit e =
8282
let swapDocumentChangeUri :: DocumentChange -> DocumentChange
83-
swapDocumentChangeUri (InL textDocEdit) = InL $ swapUri J.textDocument textDocEdit
83+
swapDocumentChangeUri (InL textDocEdit) = InL $ swapUri L.textDocument textDocEdit
8484
swapDocumentChangeUri (InR (InL createFile)) = InR $ InL $ swapUri id createFile
8585
-- for RenameFile, we swap `newUri`
86-
swapDocumentChangeUri (InR (InR (InL renameFile))) = InR $ InR $ InL $ J.newUri .~ f (renameFile ^. J.newUri) $ renameFile
86+
swapDocumentChangeUri (InR (InR (InL renameFile))) = InR $ InR $ InL $ L.newUri .~ f (renameFile ^. L.newUri) $ renameFile
8787
swapDocumentChangeUri (InR (InR (InR deleteFile))) = InR $ InR $ InR $ swapUri id deleteFile
88-
in e & J.changes . _Just %~ swapKeys f
89-
& J.documentChanges . _Just . traversed%~ swapDocumentChangeUri
88+
in e & L.changes . _Just %~ swapKeys f
89+
& L.documentChanges . _Just . traversed%~ swapDocumentChangeUri
9090

9191
swapKeys :: (Uri -> Uri) -> M.Map Uri b -> M.Map Uri b
9292
swapKeys f = M.foldlWithKey' (\acc k v -> M.insert (f k) v acc) M.empty
9393

94-
swapUri :: J.HasUri b Uri => Lens' a b -> a -> a
94+
swapUri :: L.HasUri b Uri => Lens' a b -> a -> a
9595
swapUri lens x =
96-
let newUri = f (x ^. lens . J.uri)
97-
in (lens . J.uri) .~ newUri $ x
96+
let newUri = f (x ^. lens . L.uri)
97+
in (lens . L.uri) .~ newUri $ x
9898

9999
-- | Transforms rootUri/rootPath.
100100
transformInit :: InitializeParams -> InitializeParams
@@ -105,5 +105,5 @@ mapUris f event =
105105
in case uriToFilePath (f uri) of
106106
Just fp -> T.pack fp
107107
Nothing -> p
108-
in x & J.rootUri . _L %~ f
109-
& J.rootPath . _Just . _L %~ modifyRootPath
108+
in x & L.rootUri . _L %~ f
109+
& L.rootPath . _Just . _L %~ modifyRootPath

0 commit comments

Comments
 (0)