11{-# LANGUAGE DataKinds #-}
2+ {-# LANGUAGE DuplicateRecordFields #-}
23{-# LANGUAGE GADTs #-}
4+ {-# LANGUAGE OverloadedLabels #-}
35{-# LANGUAGE OverloadedStrings #-}
46{-# LANGUAGE ViewPatterns #-}
57
@@ -14,10 +16,13 @@ import Control.Lens hiding (Iso, List)
1416import Control.Monad
1517import Control.Monad.IO.Class
1618import Data.Aeson qualified as J
19+ import Data.Generics.Labels ()
20+ import Data.Generics.Product.Fields (field' )
1721import Data.Maybe
1822import 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 )
2126import Language.LSP.Protocol.Types
2227import Language.LSP.Server
2328import Language.LSP.Test qualified as Test
@@ -90,36 +95,36 @@ spec = do
9095 -- has happened and the server has been able to send us a begin message
9196 skipManyTill Test. anyMessage $ do
9297 x <- Test. message SMethod_Progress
93- guard $ has (L. params . L. value . _workDoneProgressBegin ) x
98+ guard $ has (field' @ " params" . # value . workDoneProgressBegin ) x
9499
95100 -- allow the hander to send us updates
96101 liftIO $ signalBarrier startBarrier ()
97102
98103 do
99104 u <- Test. message SMethod_Progress
100105 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 )
103108 liftIO $ signalBarrier b1 ()
104109
105110 do
106111 u <- Test. message SMethod_Progress
107112 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 )
110115 liftIO $ signalBarrier b2 ()
111116
112117 do
113118 u <- Test. message SMethod_Progress
114119 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 )
117122 liftIO $ signalBarrier b3 ()
118123
119124 -- Then make sure we get a $/progress end notification
120125 skipManyTill Test. anyMessage $ do
121126 x <- Test. message SMethod_Progress
122- guard $ has (L. params . L. value . _workDoneProgressEnd ) x
127+ guard $ has (field' @ " params" . # value . workDoneProgressEnd ) x
123128
124129 it " handles cancellation" $ do
125130 wasCancelled <- newMVar False
@@ -150,19 +155,19 @@ spec = do
150155 -- Wait until we have created the progress so the updates will be sent individually
151156 token <- skipManyTill Test. anyMessage $ do
152157 x <- Test. message SMethod_WindowWorkDoneProgressCreate
153- pure $ x ^. L. params . L. token
158+ pure $ x ^. field' @ " params" . # token
154159
155160 -- First make sure that we get a $/progress begin notification
156161 skipManyTill Test. anyMessage $ do
157162 x <- Test. message SMethod_Progress
158- guard $ has (L. params . L. value . _workDoneProgressBegin ) x
163+ guard $ has (field' @ " params" . # value . workDoneProgressBegin ) x
159164
160165 Test. sendNotification SMethod_WindowWorkDoneProgressCancel (WorkDoneProgressCancelParams token)
161166
162167 -- Then make sure we still get a $/progress end notification
163168 skipManyTill Test. anyMessage $ do
164169 x <- Test. message SMethod_Progress
165- guard $ has (L. params . L. value . _workDoneProgressEnd ) x
170+ guard $ has (field' @ " params" . # value . workDoneProgressEnd ) x
166171
167172 c <- readMVar wasCancelled
168173 c `shouldBe` True
@@ -194,15 +199,15 @@ spec = do
194199 -- First make sure that we get a $/progress begin notification
195200 skipManyTill Test. anyMessage $ do
196201 x <- Test. message SMethod_Progress
197- guard $ has (L. params . L. value . _workDoneProgressBegin ) x
202+ guard $ has (field' @ " params" . # value . workDoneProgressBegin ) x
198203
199204 -- Then kill the thread
200205 liftIO $ putMVar killVar ()
201206
202207 -- Then make sure we still get a $/progress end notification
203208 skipManyTill Test. anyMessage $ do
204209 x <- Test. message SMethod_Progress
205- guard $ has (L. params . L. value . _workDoneProgressEnd ) x
210+ guard $ has (field' @ " params" . # value . workDoneProgressEnd ) x
206211
207212 describe " client-initiated progress reporting" $ do
208213 it " sends updates" $ do
@@ -226,7 +231,7 @@ spec = do
226231 handlers :: Handlers (LspM () )
227232 handlers =
228233 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
230235 liftIO $ waitBarrier startBarrier
231236 updater $ ProgressAmount (Just 25 ) (Just " step1" )
232237 liftIO $ waitBarrier b1
@@ -241,35 +246,35 @@ spec = do
241246 -- First make sure that we get a $/progress begin notification
242247 skipManyTill Test. anyMessage $ do
243248 x <- Test. message SMethod_Progress
244- guard $ has (L. params . L. value . _workDoneProgressBegin ) x
249+ guard $ has (field' @ " params" . # value . workDoneProgressBegin ) x
245250
246251 liftIO $ signalBarrier startBarrier ()
247252
248253 do
249254 u <- Test. message SMethod_Progress
250255 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 )
253258 liftIO $ signalBarrier b1 ()
254259
255260 do
256261 u <- Test. message SMethod_Progress
257262 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 )
260265 liftIO $ signalBarrier b2 ()
261266
262267 do
263268 u <- Test. message SMethod_Progress
264269 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 )
267272 liftIO $ signalBarrier b3 ()
268273
269274 -- Then make sure we get a $/progress end notification
270275 skipManyTill Test. anyMessage $ do
271276 x <- Test. message SMethod_Progress
272- guard $ has (L. params . L. value . _workDoneProgressEnd ) x
277+ guard $ has (field' @ " params" . # value . workDoneProgressEnd ) x
273278
274279 describe " workspace folders" $
275280 it " keeps track of open workspace folders" $ do
0 commit comments