Skip to content

Commit 3950181

Browse files
committed
Unify both generated and custom lenses
1 parent 5d174ac commit 3950181

File tree

23 files changed

+132
-105
lines changed

23 files changed

+132
-105
lines changed

lsp-test/func-test/FuncTest.hs

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -4,9 +4,9 @@ module Main where
44

55
import Language.LSP.Server
66
import qualified Language.LSP.Test as Test
7-
import Language.LSP.Protocol.Types hiding (error)
8-
import Language.LSP.Protocol.Types.Lens hiding (options)
9-
import Language.LSP.Protocol.Message hiding (options, error)
7+
import Language.LSP.Protocol.Types
8+
import qualified Language.LSP.Protocol.Lens as J
9+
import Language.LSP.Protocol.Message
1010
import Control.Monad.IO.Class
1111
import System.IO
1212
import Control.Monad
@@ -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 (params . value . _workDoneProgressBegin) x
60+
guard $ has (J.params . J.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 (params . value . _workDoneProgressEnd) x
68+
guard $ has (J.params . J.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: 10 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -118,9 +118,8 @@ import Data.Default
118118
import Data.List
119119
import Data.Maybe
120120
import Language.LSP.Protocol.Types
121-
import Language.LSP.Protocol.Message hiding (id)
122-
import qualified Language.LSP.Protocol.Types.Lens as J
123-
import qualified Language.LSP.Protocol.Message as LSP
121+
import Language.LSP.Protocol.Message
122+
import qualified Language.LSP.Protocol.Lens as J
124123
import qualified Language.LSP.Protocol.Capabilities as C
125124
import Language.LSP.VFS
126125
import Language.LSP.Test.Compat
@@ -228,7 +227,7 @@ runSessionWithHandles' serverProc serverIn serverOut config' caps rootDir sessio
228227
-- collect them and then...
229228
(inBetween, initRspMsg) <- manyTill_ anyMessage (responseForId SMethod_Initialize initReqId)
230229

231-
case initRspMsg ^. LSP.result of
230+
case initRspMsg ^. J.result of
232231
Left error -> liftIO $ putStrLn ("Error while initializing: " ++ show error)
233232
Right _ -> pure ()
234233

@@ -307,13 +306,13 @@ getDocumentEdit doc = do
307306
documentContents doc
308307
where
309308
checkDocumentChanges req =
310-
let changes = req ^. params . J.edit . J.documentChanges
309+
let changes = req ^. J.params . J.edit . J.documentChanges
311310
maybeDocs = fmap (fmap documentChangeUri) changes
312311
in case maybeDocs of
313312
Just docs -> (doc ^. J.uri) `elem` docs
314313
Nothing -> False
315314
checkChanges req =
316-
let mMap = req ^. params . J.edit . J.changes
315+
let mMap = req ^. J.params . J.edit . J.changes
317316
in maybe False (Map.member (doc ^. J.uri)) mMap
318317

319318
-- | Sends a request to the server and waits for its response.
@@ -433,7 +432,7 @@ createDoc file languageId contents = do
433432
createHits _ = False
434433

435434
regHits :: TRegistration Method_WorkspaceDidChangeWatchedFiles -> Bool
436-
regHits reg = foldl' (\acc w -> acc || watchHits w) False (reg ^. registerOptions . _Just . J.watchers)
435+
regHits reg = foldl' (\acc w -> acc || watchHits w) False (reg ^. J.registerOptions . _Just . J.watchers)
437436

438437
clientCapsSupports =
439438
caps ^? J.workspace . _Just . J.didChangeWatchedFiles . _Just . J.dynamicRegistration . _Just
@@ -489,7 +488,7 @@ getDocUri file = do
489488
waitForDiagnostics :: Session [Diagnostic]
490489
waitForDiagnostics = do
491490
diagsNot <- skipManyTill anyMessage (message SMethod_TextDocumentPublishDiagnostics)
492-
let diags = diagsNot ^. params . J.diagnostics
491+
let diags = diagsNot ^. J.params . J.diagnostics
493492
return diags
494493

495494
-- | The same as 'waitForDiagnostics', but will only match a specific
@@ -511,7 +510,7 @@ waitForDiagnosticsSource src = do
511510
noDiagnostics :: Session ()
512511
noDiagnostics = do
513512
diagsNot <- message SMethod_TextDocumentPublishDiagnostics
514-
when (diagsNot ^. params . J.diagnostics /= []) $ liftIO $ throw UnexpectedDiagnostics
513+
when (diagsNot ^. J.params . J.diagnostics /= []) $ liftIO $ throw UnexpectedDiagnostics
515514

516515
-- | Returns the symbols in a document.
517516
getDocumentSymbols :: TextDocumentIdentifier -> Session (Either [SymbolInformation] [DocumentSymbol])
@@ -529,7 +528,7 @@ getCodeActions doc range = do
529528
ctx <- getCodeActionContextInRange doc range
530529
rsp <- request SMethod_TextDocumentCodeAction (CodeActionParams Nothing Nothing doc range ctx)
531530

532-
case rsp ^. result of
531+
case rsp ^. J.result of
533532
Right (InL xs) -> return xs
534533
Right (InR _) -> return []
535534
Left error -> throw (UnexpectedResponseError (SomeLspId $ fromJust $ rsp ^. J.id) error)
@@ -722,7 +721,7 @@ getHighlights doc pos =
722721
-- Returns the result if successful.
723722
getResponseResult :: (ToJSON (ErrorData m)) => TResponseMessage m -> MessageResult m
724723
getResponseResult rsp =
725-
case rsp ^. result of
724+
case rsp ^. J.result of
726725
Right x -> x
727726
Left err -> throw $ UnexpectedResponseError (SomeLspId $ fromJust $ rsp ^. J.id) err
728727

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

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -15,8 +15,8 @@ import qualified Data.ByteString.Lazy.Char8 as B
1515
import Data.Maybe
1616
import System.IO
1717
import System.IO.Error
18-
import Language.LSP.Protocol.Message hiding (error)
19-
import qualified Language.LSP.Protocol.Types.Lens as J
18+
import Language.LSP.Protocol.Message
19+
import qualified Language.LSP.Protocol.Lens as J
2020
import Language.LSP.Test.Exceptions
2121

2222
import Data.IxMap

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

Lines changed: 26 additions & 26 deletions
Original file line numberDiff line numberDiff line change
@@ -10,11 +10,11 @@ module Language.LSP.Test.Files
1010
)
1111
where
1212

13-
import Language.LSP.Protocol.Message hiding (error, id)
13+
import Language.LSP.Protocol.Message
1414
import Language.LSP.Protocol.Types
15-
import Language.LSP.Protocol.Types.Lens hiding (id)
15+
import qualified Language.LSP.Protocol.Lens as J
1616
import Control.Lens
17-
import qualified Data.Map.Strict as M
17+
import qualified Data.Map.Strict as M
1818
import qualified Data.Text as T
1919
import Data.Maybe
2020
import System.Directory
@@ -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 ^. params . rootUri of
44+
rootUri <- case req ^. J.params . J.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 $ params .~ transformInit (r ^. params) $ r
59-
fromClientMsg (FromClientMess m@SMethod_TextDocumentDidOpen n) = FromClientMess m $ swapUri (params . textDocument) n
60-
fromClientMsg (FromClientMess m@SMethod_TextDocumentDidChange n) = FromClientMess m $ swapUri (params . textDocument) n
61-
fromClientMsg (FromClientMess m@SMethod_TextDocumentWillSave n) = FromClientMess m $ swapUri (params . textDocument) n
62-
fromClientMsg (FromClientMess m@SMethod_TextDocumentDidSave n) = FromClientMess m $ swapUri (params . textDocument) n
63-
fromClientMsg (FromClientMess m@SMethod_TextDocumentDidClose n) = FromClientMess m $ swapUri (params . textDocument) n
64-
fromClientMsg (FromClientMess m@SMethod_TextDocumentDocumentSymbol n) = FromClientMess m $ swapUri (params . textDocument) n
65-
fromClientMsg (FromClientMess m@SMethod_TextDocumentRename n) = FromClientMess m $ swapUri (params . textDocument) n
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
6666
fromClientMsg x = x
6767

6868
fromServerMsg :: FromServerMessage -> FromServerMessage
69-
fromServerMsg (FromServerMess m@SMethod_WorkspaceApplyEdit r) = FromServerMess m $ params . edit .~ swapWorkspaceEdit (r ^. params . edit) $ r
70-
fromServerMsg (FromServerMess m@SMethod_TextDocumentPublishDiagnostics n) = FromServerMess m $ swapUri params n
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
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 location <$> si)
76-
in FromServerRsp m $ r & result . _Right %~ swapUri'
77-
fromServerMsg (FromServerRsp m@SMethod_TextDocumentRename r) = FromServerRsp m $ r & result . _Right . _L %~ swapWorkspaceEdit
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
7878
fromServerMsg x = x
7979

8080
swapWorkspaceEdit :: WorkspaceEdit -> WorkspaceEdit
8181
swapWorkspaceEdit e =
8282
let swapDocumentChangeUri :: DocumentChange -> DocumentChange
83-
swapDocumentChangeUri (InL textDocEdit) = InL $ swapUri textDocument textDocEdit
83+
swapDocumentChangeUri (InL textDocEdit) = InL $ swapUri J.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 $ newUri .~ f (renameFile ^. newUri) $ renameFile
86+
swapDocumentChangeUri (InR (InR (InL renameFile))) = InR $ InR $ InL $ J.newUri .~ f (renameFile ^. J.newUri) $ renameFile
8787
swapDocumentChangeUri (InR (InR (InR deleteFile))) = InR $ InR $ InR $ swapUri id deleteFile
88-
in e & changes . _Just %~ swapKeys f
89-
& documentChanges . _Just . traversed%~ swapDocumentChangeUri
88+
in e & J.changes . _Just %~ swapKeys f
89+
& J.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 :: HasUri b Uri => Lens' a b -> a -> a
94+
swapUri :: J.HasUri b Uri => Lens' a b -> a -> a
9595
swapUri lens x =
96-
let newUri = f (x ^. lens . uri)
97-
in (lens . uri) .~ newUri $ x
96+
let newUri = f (x ^. lens . J.uri)
97+
in (lens . J.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 & rootUri . _L %~ f
109-
& rootPath . _Just . _L %~ modifyRootPath
108+
in x & J.rootUri . _L %~ f
109+
& J.rootPath . _Just . _L %~ modifyRootPath

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

Lines changed: 1 addition & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,6 @@
11
{-# LANGUAGE MultiParamTypeClasses #-}
2-
{-# LANGUAGE EmptyCase #-}
3-
{-# LANGUAGE TypeOperators #-}
42
{-# LANGUAGE ScopedTypeVariables #-}
53
{-# LANGUAGE TypeInType #-}
6-
{-# LANGUAGE KindSignatures #-}
7-
{-# LANGUAGE TypeInType #-}
84
{-# LANGUAGE GADTs #-}
95
{-# LANGUAGE LambdaCase #-}
106
{-# LANGUAGE RankNTypes #-}
@@ -35,7 +31,7 @@ import Data.Conduit.Parser hiding (named)
3531
import qualified Data.Conduit.Parser (named)
3632
import qualified Data.Text as T
3733
import Data.Typeable
38-
import Language.LSP.Protocol.Message hiding (error)
34+
import Language.LSP.Protocol.Message
3935
import Language.LSP.Test.Session
4036
import GHC.TypeLits (KnownSymbol, symbolVal)
4137
import Data.GADT.Compare

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

Lines changed: 12 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -65,8 +65,8 @@ import qualified Data.Text.IO as T
6565
import Data.Maybe
6666
import Data.Function
6767
import Language.LSP.Protocol.Types as LSP
68-
import qualified Language.LSP.Protocol.Types.Lens as J
69-
import Language.LSP.Protocol.Message as LSP hiding (error)
68+
import qualified Language.LSP.Protocol.Lens as J
69+
import Language.LSP.Protocol.Message as LSP
7070
import Language.LSP.VFS
7171
import Language.LSP.Test.Compat
7272
import Language.LSP.Test.Decoding
@@ -322,47 +322,47 @@ documentChangeUri (InR (InR (InR x))) = x ^. J.uri
322322

323323
updateState :: (MonadIO m, HasReader SessionContext m, HasState SessionState m)
324324
=> FromServerMessage -> m ()
325-
updateState (FromServerMess SMethod_Progress req) = case req ^. params . J.value of
325+
updateState (FromServerMess SMethod_Progress req) = case req ^. J.params . J.value of
326326
v | Just _ <- v ^? _workDoneProgressBegin ->
327-
modify $ \s -> s { curProgressSessions = Set.insert (req ^. params . J.token) $ curProgressSessions s }
327+
modify $ \s -> s { curProgressSessions = Set.insert (req ^. J.params . J.token) $ curProgressSessions s }
328328
v | Just _ <- v ^? _workDoneProgressEnd ->
329-
modify $ \s -> s { curProgressSessions = Set.delete (req ^. params . J.token) $ curProgressSessions s }
329+
modify $ \s -> s { curProgressSessions = Set.delete (req ^. J.params . J.token) $ curProgressSessions s }
330330
_ -> pure ()
331331

332332
-- Keep track of dynamic capability registration
333333
updateState (FromServerMess SMethod_ClientRegisterCapability req) = do
334334
let
335335
regs :: [SomeRegistration]
336-
regs = req ^.. params . J.registrations . traversed . to toSomeRegistration . _Just
337-
let newRegs = (\sr@(SomeRegistration r) -> (r ^. LSP.id, sr)) <$> regs
336+
regs = req ^.. J.params . J.registrations . traversed . to toSomeRegistration . _Just
337+
let newRegs = (\sr@(SomeRegistration r) -> (r ^. J.id, sr)) <$> regs
338338
modify $ \s ->
339339
s { curDynCaps = Map.union (Map.fromList newRegs) (curDynCaps s) }
340340

341341
updateState (FromServerMess SMethod_ClientUnregisterCapability req) = do
342-
let unRegs = (^. J.id) <$> req ^. params . J.unregisterations
342+
let unRegs = (^. J.id) <$> req ^. J.params . J.unregisterations
343343
modify $ \s ->
344344
let newCurDynCaps = foldr' Map.delete (curDynCaps s) unRegs
345345
in s { curDynCaps = newCurDynCaps }
346346

347347
updateState (FromServerMess SMethod_TextDocumentPublishDiagnostics n) = do
348-
let diags = n ^. params . J.diagnostics
349-
doc = n ^. params . J.uri
348+
let diags = n ^. J.params . J.diagnostics
349+
doc = n ^. J.params . J.uri
350350
modify $ \s ->
351351
let newDiags = Map.insert (toNormalizedUri doc) diags (curDiagnostics s)
352352
in s { curDiagnostics = newDiags }
353353

354354
updateState (FromServerMess SMethod_WorkspaceApplyEdit r) = do
355355

356356
-- First, prefer the versioned documentChanges field
357-
allChangeParams <- case r ^. params . J.edit . J.documentChanges of
357+
allChangeParams <- case r ^. J.params . J.edit . J.documentChanges of
358358
Just (cs) -> do
359359
mapM_ (checkIfNeedsOpened . documentChangeUri) cs
360360
-- replace the user provided version numbers with the VFS ones + 1
361361
-- (technically we should check that the user versions match the VFS ones)
362362
cs' <- traverseOf (traverse . _L . J.textDocument . _versionedTextDocumentIdentifier) bumpNewestVersion cs
363363
return $ mapMaybe getParamsFromDocumentChange cs'
364364
-- Then fall back to the changes field
365-
Nothing -> case r ^. params . J.edit . J.changes of
365+
Nothing -> case r ^. J.params . J.edit . J.changes of
366366
Just cs -> do
367367
mapM_ checkIfNeedsOpened (Map.keys cs)
368368
concat <$> mapM (uncurry getChangeParams) (Map.toList cs)

lsp-test/test/DummyServer.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -17,8 +17,8 @@ import UnliftIO
1717
import System.Directory
1818
import System.FilePath
1919
import System.Process
20-
import Language.LSP.Protocol.Types hiding (options)
21-
import Language.LSP.Protocol.Message hiding (error)
20+
import Language.LSP.Protocol.Types
21+
import Language.LSP.Protocol.Message
2222
import Data.Proxy
2323

2424
withDummyServer :: ((Handle, Handle) -> IO ()) -> IO ()

lsp-test/test/Test.hs

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -23,7 +23,7 @@ import Control.Lens hiding (List, Iso)
2323
import Language.LSP.Test
2424
import Language.LSP.Protocol.Message
2525
import Language.LSP.Protocol.Types
26-
import qualified Language.LSP.Protocol.Types.Lens as J
26+
import qualified Language.LSP.Protocol.Lens as J
2727
import System.Directory
2828
import System.FilePath
2929
import System.Timeout
@@ -42,7 +42,7 @@ main = hspec $ around withDummyServer $ do
4242
in session `shouldThrow` anySessionException
4343
it "initializeResponse" $ \(hin, hout) -> runSessionWithHandles hin hout def fullCaps "." $ do
4444
rsp <- initializeResponse
45-
liftIO $ rsp ^. result `shouldSatisfy` isRight
45+
liftIO $ rsp ^. J.result `shouldSatisfy` isRight
4646

4747
it "runSessionWithConfig" $ \(hin, hout) ->
4848
runSessionWithHandles hin hout def fullCaps "." $ return ()
@@ -145,7 +145,7 @@ main = hspec $ around withDummyServer $ do
145145
editReq <- message SMethod_WorkspaceApplyEdit
146146
liftIO $ do
147147
let Just [InL(TextDocumentEdit vdoc [InL edit_])] =
148-
editReq ^. params . J.edit . J.documentChanges
148+
editReq ^. J.params . J.edit . J.documentChanges
149149
vdoc `shouldBe` OptionalVersionedTextDocumentIdentifier (doc ^. J.uri) (InL beforeVersion)
150150
edit_ `shouldBe` TextEdit (Range (Position 0 0) (Position 0 5)) "howdy"
151151

@@ -172,7 +172,7 @@ main = hspec $ around withDummyServer $ do
172172

173173
editReq <- message SMethod_WorkspaceApplyEdit
174174
liftIO $ do
175-
let (Just cs) = editReq ^. params . J.edit . J.changes
175+
let (Just cs) = editReq ^. J.params . J.edit . J.changes
176176
[(u, es)] = M.toList cs
177177
u `shouldBe` doc ^. J.uri
178178
es `shouldBe` [TextEdit (Range (Position 0 0) (Position 0 5)) "howdy"]
@@ -362,7 +362,7 @@ main = hspec $ around withDummyServer $ do
362362

363363
doc <- createDoc "Foo.watch" "haskell" ""
364364
msg <- message SMethod_WindowLogMessage
365-
liftIO $ msg ^. params . J.message `shouldBe` "got workspace/didChangeWatchedFiles"
365+
liftIO $ msg ^. J.params . J.message `shouldBe` "got workspace/didChangeWatchedFiles"
366366

367367
[SomeRegistration (TRegistration _ regMethod regOpts)] <- getRegisteredCapabilities
368368
liftIO $ do
@@ -391,7 +391,7 @@ main = hspec $ around withDummyServer $ do
391391

392392
doc <- createDoc (curDir </> "Foo.watch") "haskell" ""
393393
msg <- message SMethod_WindowLogMessage
394-
liftIO $ msg ^. params . J.message `shouldBe` "got workspace/didChangeWatchedFiles"
394+
liftIO $ msg ^. J.params . J.message `shouldBe` "got workspace/didChangeWatchedFiles"
395395

396396
-- now unregister it by sending a specific createDoc
397397
createDoc ".unregister.abs" "haskell" ""

0 commit comments

Comments
 (0)