1
1
{-# LANGUAGE DataKinds #-}
2
+ {-# LANGUAGE DuplicateRecordFields #-}
2
3
{-# LANGUAGE GADTs #-}
4
+ {-# LANGUAGE OverloadedLabels #-}
3
5
{-# LANGUAGE OverloadedStrings #-}
4
6
{-# LANGUAGE ViewPatterns #-}
5
7
@@ -14,10 +16,13 @@ import Control.Lens hiding (Iso, List)
14
16
import Control.Monad
15
17
import Control.Monad.IO.Class
16
18
import Data.Aeson qualified as J
19
+ import Data.Generics.Labels ()
20
+ import Data.Generics.Product.Fields (field' )
17
21
import Data.Maybe
18
22
import Data.Proxy
19
- import Language.LSP.Protocol.Lens qualified as L
20
- import Language.LSP.Protocol.Message
23
+ import Data.Set qualified as Set
24
+ import Language.LSP.Protocol.Lens
25
+ import Language.LSP.Protocol.Message hiding (error )
21
26
import Language.LSP.Protocol.Types
22
27
import Language.LSP.Server
23
28
import Language.LSP.Test qualified as Test
@@ -90,36 +95,36 @@ spec = do
90
95
-- has happened and the server has been able to send us a begin message
91
96
skipManyTill Test. anyMessage $ do
92
97
x <- Test. message SMethod_Progress
93
- guard $ has (L. params . L. value . _workDoneProgressBegin ) x
98
+ guard $ has (field' @ " params" . # value . workDoneProgressBegin ) x
94
99
95
100
-- allow the hander to send us updates
96
101
liftIO $ signalBarrier startBarrier ()
97
102
98
103
do
99
104
u <- Test. message SMethod_Progress
100
105
liftIO $ do
101
- u ^? L. params . L. value . _workDoneProgressReport . L. message `shouldBe` Just (Just " step1" )
102
- u ^? L. params . L. value . _workDoneProgressReport . L. percentage `shouldBe` Just (Just 25 )
106
+ u ^? field' @ " params" . # value . workDoneProgressReport . # message `shouldBe` Just (Just " step1" )
107
+ u ^? field' @ " params" . # value . workDoneProgressReport . # percentage `shouldBe` Just (Just 25 )
103
108
liftIO $ signalBarrier b1 ()
104
109
105
110
do
106
111
u <- Test. message SMethod_Progress
107
112
liftIO $ do
108
- u ^? L. params . L. value . _workDoneProgressReport . L. message `shouldBe` Just (Just " step2" )
109
- u ^? L. params . L. value . _workDoneProgressReport . L. percentage `shouldBe` Just (Just 50 )
113
+ u ^? field' @ " params" . # value . workDoneProgressReport . # message `shouldBe` Just (Just " step2" )
114
+ u ^? field' @ " params" . # value . workDoneProgressReport . # percentage `shouldBe` Just (Just 50 )
110
115
liftIO $ signalBarrier b2 ()
111
116
112
117
do
113
118
u <- Test. message SMethod_Progress
114
119
liftIO $ do
115
- u ^? L. params . L. value . _workDoneProgressReport . L. message `shouldBe` Just (Just " step3" )
116
- u ^? L. params . L. value . _workDoneProgressReport . L. percentage `shouldBe` Just (Just 75 )
120
+ u ^? field' @ " params" . # value . workDoneProgressReport . # message `shouldBe` Just (Just " step3" )
121
+ u ^? field' @ " params" . # value . workDoneProgressReport . # percentage `shouldBe` Just (Just 75 )
117
122
liftIO $ signalBarrier b3 ()
118
123
119
124
-- Then make sure we get a $/progress end notification
120
125
skipManyTill Test. anyMessage $ do
121
126
x <- Test. message SMethod_Progress
122
- guard $ has (L. params . L. value . _workDoneProgressEnd ) x
127
+ guard $ has (field' @ " params" . # value . workDoneProgressEnd ) x
123
128
124
129
it " handles cancellation" $ do
125
130
wasCancelled <- newMVar False
@@ -150,19 +155,19 @@ spec = do
150
155
-- Wait until we have created the progress so the updates will be sent individually
151
156
token <- skipManyTill Test. anyMessage $ do
152
157
x <- Test. message SMethod_WindowWorkDoneProgressCreate
153
- pure $ x ^. L. params . L. token
158
+ pure $ x ^. field' @ " params" . # token
154
159
155
160
-- First make sure that we get a $/progress begin notification
156
161
skipManyTill Test. anyMessage $ do
157
162
x <- Test. message SMethod_Progress
158
- guard $ has (L. params . L. value . _workDoneProgressBegin ) x
163
+ guard $ has (field' @ " params" . # value . workDoneProgressBegin ) x
159
164
160
165
Test. sendNotification SMethod_WindowWorkDoneProgressCancel (WorkDoneProgressCancelParams token)
161
166
162
167
-- Then make sure we still get a $/progress end notification
163
168
skipManyTill Test. anyMessage $ do
164
169
x <- Test. message SMethod_Progress
165
- guard $ has (L. params . L. value . _workDoneProgressEnd ) x
170
+ guard $ has (field' @ " params" . # value . workDoneProgressEnd ) x
166
171
167
172
c <- readMVar wasCancelled
168
173
c `shouldBe` True
@@ -194,15 +199,15 @@ spec = do
194
199
-- First make sure that we get a $/progress begin notification
195
200
skipManyTill Test. anyMessage $ do
196
201
x <- Test. message SMethod_Progress
197
- guard $ has (L. params . L. value . _workDoneProgressBegin ) x
202
+ guard $ has (field' @ " params" . # value . workDoneProgressBegin ) x
198
203
199
204
-- Then kill the thread
200
205
liftIO $ putMVar killVar ()
201
206
202
207
-- Then make sure we still get a $/progress end notification
203
208
skipManyTill Test. anyMessage $ do
204
209
x <- Test. message SMethod_Progress
205
- guard $ has (L. params . L. value . _workDoneProgressEnd ) x
210
+ guard $ has (field' @ " params" . # value . workDoneProgressEnd ) x
206
211
207
212
describe " client-initiated progress reporting" $ do
208
213
it " sends updates" $ do
@@ -226,7 +231,7 @@ spec = do
226
231
handlers :: Handlers (LspM () )
227
232
handlers =
228
233
requestHandler SMethod_TextDocumentCodeLens $ \ req resp -> void $ forkIO $ do
229
- withProgress " Doing something" (req ^. L. params . L. workDoneToken) NotCancellable $ \ updater -> do
234
+ withProgress " Doing something" (req ^. field' @ " params" . # workDoneToken) NotCancellable $ \ updater -> do
230
235
liftIO $ waitBarrier startBarrier
231
236
updater $ ProgressAmount (Just 25 ) (Just " step1" )
232
237
liftIO $ waitBarrier b1
@@ -241,35 +246,35 @@ spec = do
241
246
-- First make sure that we get a $/progress begin notification
242
247
skipManyTill Test. anyMessage $ do
243
248
x <- Test. message SMethod_Progress
244
- guard $ has (L. params . L. value . _workDoneProgressBegin ) x
249
+ guard $ has (field' @ " params" . # value . workDoneProgressBegin ) x
245
250
246
251
liftIO $ signalBarrier startBarrier ()
247
252
248
253
do
249
254
u <- Test. message SMethod_Progress
250
255
liftIO $ do
251
- u ^? L. params . L. value . _workDoneProgressReport . L. message `shouldBe` Just (Just " step1" )
252
- u ^? L. params . L. value . _workDoneProgressReport . L. percentage `shouldBe` Just (Just 25 )
256
+ u ^? field' @ " params" . # value . workDoneProgressReport . # message `shouldBe` Just (Just " step1" )
257
+ u ^? field' @ " params" . # value . workDoneProgressReport . # percentage `shouldBe` Just (Just 25 )
253
258
liftIO $ signalBarrier b1 ()
254
259
255
260
do
256
261
u <- Test. message SMethod_Progress
257
262
liftIO $ do
258
- u ^? L. params . L. value . _workDoneProgressReport . L. message `shouldBe` Just (Just " step2" )
259
- u ^? L. params . L. value . _workDoneProgressReport . L. percentage `shouldBe` Just (Just 50 )
263
+ u ^? field' @ " params" . # value . workDoneProgressReport . # message `shouldBe` Just (Just " step2" )
264
+ u ^? field' @ " params" . # value . workDoneProgressReport . # percentage `shouldBe` Just (Just 50 )
260
265
liftIO $ signalBarrier b2 ()
261
266
262
267
do
263
268
u <- Test. message SMethod_Progress
264
269
liftIO $ do
265
- u ^? L. params . L. value . _workDoneProgressReport . L. message `shouldBe` Just (Just " step3" )
266
- u ^? L. params . L. value . _workDoneProgressReport . L. percentage `shouldBe` Just (Just 75 )
270
+ u ^? field' @ " params" . # value . workDoneProgressReport . # message `shouldBe` Just (Just " step3" )
271
+ u ^? field' @ " params" . # value . workDoneProgressReport . # percentage `shouldBe` Just (Just 75 )
267
272
liftIO $ signalBarrier b3 ()
268
273
269
274
-- Then make sure we get a $/progress end notification
270
275
skipManyTill Test. anyMessage $ do
271
276
x <- Test. message SMethod_Progress
272
- guard $ has (L. params . L. value . _workDoneProgressEnd ) x
277
+ guard $ has (field' @ " params" . # value . workDoneProgressEnd ) x
273
278
274
279
describe " workspace folders" $
275
280
it " keeps track of open workspace folders" $ do
0 commit comments