@@ -8,6 +8,7 @@ module Main where
8
8
import Colog.Core
9
9
import Colog.Core qualified as L
10
10
import Control.Applicative.Combinators
11
+ import Control.Concurrent.Extra (newBarrier , signalBarrier , waitBarrier )
11
12
import Control.Exception
12
13
import Control.Lens hiding (Iso , List )
13
14
import Control.Monad
@@ -53,7 +54,10 @@ spec = do
53
54
let logger = L. cmap show L. logStringStderr
54
55
describe " server-initiated progress reporting" $ do
55
56
it " sends updates" $ do
56
- startBarrier <- newEmptyMVar
57
+ startBarrier <- newBarrier
58
+ b1 <- newBarrier
59
+ b2 <- newBarrier
60
+ b3 <- newBarrier
57
61
58
62
let definition =
59
63
ServerDefinition
@@ -71,10 +75,13 @@ spec = do
71
75
handlers =
72
76
requestHandler (SMethod_CustomMethod (Proxy @ " something" )) $ \ _req resp -> void $ forkIO $ do
73
77
withProgress " Doing something" Nothing NotCancellable $ \ updater -> do
74
- takeMVar startBarrier
78
+ liftIO $ waitBarrier startBarrier
75
79
updater $ ProgressAmount (Just 25 ) (Just " step1" )
80
+ liftIO $ waitBarrier b1
76
81
updater $ ProgressAmount (Just 50 ) (Just " step2" )
82
+ liftIO $ waitBarrier b2
77
83
updater $ ProgressAmount (Just 75 ) (Just " step3" )
84
+ liftIO $ waitBarrier b3
78
85
79
86
runSessionWithServer logger definition Test. defaultConfig Test. fullCaps " ." $ do
80
87
Test. sendRequest (SMethod_CustomMethod (Proxy @ " something" )) J. Null
@@ -86,25 +93,28 @@ spec = do
86
93
guard $ has (L. params . L. value . _workDoneProgressBegin) x
87
94
88
95
-- allow the hander to send us updates
89
- putMVar startBarrier ()
96
+ liftIO $ signalBarrier startBarrier ()
90
97
91
98
do
92
99
u <- Test. message SMethod_Progress
93
100
liftIO $ do
94
101
u ^? L. params . L. value . _workDoneProgressReport . L. message `shouldBe` Just (Just " step1" )
95
102
u ^? L. params . L. value . _workDoneProgressReport . L. percentage `shouldBe` Just (Just 25 )
103
+ liftIO $ signalBarrier b1 ()
96
104
97
105
do
98
106
u <- Test. message SMethod_Progress
99
107
liftIO $ do
100
108
u ^? L. params . L. value . _workDoneProgressReport . L. message `shouldBe` Just (Just " step2" )
101
109
u ^? L. params . L. value . _workDoneProgressReport . L. percentage `shouldBe` Just (Just 50 )
110
+ liftIO $ signalBarrier b2 ()
102
111
103
112
do
104
113
u <- Test. message SMethod_Progress
105
114
liftIO $ do
106
115
u ^? L. params . L. value . _workDoneProgressReport . L. message `shouldBe` Just (Just " step3" )
107
116
u ^? L. params . L. value . _workDoneProgressReport . L. percentage `shouldBe` Just (Just 75 )
117
+ liftIO $ signalBarrier b3 ()
108
118
109
119
-- Then make sure we get a $/progress end notification
110
120
skipManyTill Test. anyMessage $ do
@@ -132,7 +142,7 @@ spec = do
132
142
-- Doesn't matter what cancellability we set here!
133
143
withProgress " Doing something" Nothing NotCancellable $ \ updater -> do
134
144
-- Wait around to be cancelled, set the MVar only if we are
135
- liftIO $ threadDelay (1 * 1000000 ) `Control.Exception.catch` (\ (e :: ProgressCancelledException ) -> modifyMVar_ wasCancelled (\ _ -> pure True ))
145
+ liftIO $ threadDelay (5 * 1000000 ) `Control.Exception.catch` (\ (e :: ProgressCancelledException ) -> modifyMVar_ wasCancelled (\ _ -> pure True ))
136
146
137
147
runSessionWithServer logger definition Test. defaultConfig Test. fullCaps " ." $ do
138
148
Test. sendRequest (SMethod_CustomMethod (Proxy @ " something" )) J. Null
@@ -196,6 +206,11 @@ spec = do
196
206
197
207
describe " client-initiated progress reporting" $ do
198
208
it " sends updates" $ do
209
+ startBarrier <- newBarrier
210
+ b1 <- newBarrier
211
+ b2 <- newBarrier
212
+ b3 <- newBarrier
213
+
199
214
let definition =
200
215
ServerDefinition
201
216
{ parseConfig = const $ const $ Right ()
@@ -212,9 +227,13 @@ spec = do
212
227
handlers =
213
228
requestHandler SMethod_TextDocumentCodeLens $ \ req resp -> void $ forkIO $ do
214
229
withProgress " Doing something" (req ^. L. params . L. workDoneToken) NotCancellable $ \ updater -> do
230
+ liftIO $ waitBarrier startBarrier
215
231
updater $ ProgressAmount (Just 25 ) (Just " step1" )
232
+ liftIO $ waitBarrier b1
216
233
updater $ ProgressAmount (Just 50 ) (Just " step2" )
234
+ liftIO $ waitBarrier b2
217
235
updater $ ProgressAmount (Just 75 ) (Just " step3" )
236
+ liftIO $ waitBarrier b3
218
237
219
238
runSessionWithServer logger definition Test. defaultConfig Test. fullCaps " ." $ do
220
239
Test. sendRequest SMethod_TextDocumentCodeLens (CodeLensParams (Just $ ProgressToken $ InR " hello" ) Nothing (TextDocumentIdentifier $ Uri " ." ))
@@ -224,23 +243,28 @@ spec = do
224
243
x <- Test. message SMethod_Progress
225
244
guard $ has (L. params . L. value . _workDoneProgressBegin) x
226
245
246
+ liftIO $ signalBarrier startBarrier ()
247
+
227
248
do
228
249
u <- Test. message SMethod_Progress
229
250
liftIO $ do
230
251
u ^? L. params . L. value . _workDoneProgressReport . L. message `shouldBe` Just (Just " step1" )
231
252
u ^? L. params . L. value . _workDoneProgressReport . L. percentage `shouldBe` Just (Just 25 )
253
+ liftIO $ signalBarrier b1 ()
232
254
233
255
do
234
256
u <- Test. message SMethod_Progress
235
257
liftIO $ do
236
258
u ^? L. params . L. value . _workDoneProgressReport . L. message `shouldBe` Just (Just " step2" )
237
259
u ^? L. params . L. value . _workDoneProgressReport . L. percentage `shouldBe` Just (Just 50 )
260
+ liftIO $ signalBarrier b2 ()
238
261
239
262
do
240
263
u <- Test. message SMethod_Progress
241
264
liftIO $ do
242
265
u ^? L. params . L. value . _workDoneProgressReport . L. message `shouldBe` Just (Just " step3" )
243
266
u ^? L. params . L. value . _workDoneProgressReport . L. percentage `shouldBe` Just (Just 75 )
267
+ liftIO $ signalBarrier b3 ()
244
268
245
269
-- Then make sure we get a $/progress end notification
246
270
skipManyTill Test. anyMessage $ do
0 commit comments