@@ -5,23 +5,33 @@ module Dependency where
5
5
6
6
import qualified Control.Applicative as Applicative
7
7
import Control.Applicative.Combinators (skipManyTill )
8
+ import Control.Lens (preview , (^.) )
8
9
import Control.Monad.IO.Class (liftIO )
9
10
import qualified Data.Aeson as A
10
11
import Data.Bool (bool )
11
12
import Data.List (isSuffixOf )
12
13
import Data.Maybe (fromMaybe )
13
14
import Data.Proxy (Proxy (.. ))
15
+ import Data.Text (isPrefixOf )
14
16
import Development.IDE.GHC.Compat (GhcVersion (.. ))
15
- import Language.LSP.Protocol.Message (TCustomMessage (NotMess ),
17
+ import qualified Language.LSP.Protocol.Lens as L
18
+ import Language.LSP.Protocol.Message (FromServerMessage' (FromServerMess ),
19
+ SMethod (SMethod_Progress , SMethod_TextDocumentPublishDiagnostics ),
20
+ TCustomMessage (NotMess ),
16
21
TNotificationMessage (.. ))
17
- import Language.LSP.Protocol.Types (Definition (.. ),
22
+ import Language.LSP.Protocol.Types (Definition (.. ), Diagnostic ,
18
23
Location (.. ), Position (.. ),
24
+ ProgressParams (.. ),
19
25
Range (.. ),
26
+ WorkDoneProgressEnd (.. ),
27
+ _workDoneProgressEnd ,
20
28
type (|? ) (InL , InR ),
21
29
uriToFilePath )
22
30
import Language.LSP.Test (Session , anyMessage ,
23
31
customNotification ,
24
- getDefinitions , openDoc )
32
+ getDefinitions , message ,
33
+ openDoc , satisfyMaybe ,
34
+ waitForDiagnostics )
25
35
import System.FilePath (splitDirectories , (<.>) ,
26
36
(</>) )
27
37
import Test.Tasty (TestTree , testGroup )
@@ -58,6 +68,27 @@ fileDoneIndexing fpSuffix =
58
68
fpSuffix `isSuffixOf` fpDirs
59
69
other -> error $ " Failed to parse ghcide/reference/ready file: " <> show other
60
70
71
+ waitForDiagnosticsOrDoneIndexing :: Session [Diagnostic ]
72
+ waitForDiagnosticsOrDoneIndexing =
73
+ skipManyTill anyMessage (diagnosticsMessage Applicative. <|> doneIndexing)
74
+ where
75
+ diagnosticsMessage :: Session [Diagnostic ]
76
+ diagnosticsMessage = do
77
+ diagnosticsNotification <- message SMethod_TextDocumentPublishDiagnostics
78
+ let diagnosticss = diagnosticsNotification ^. L. params . L. diagnostics
79
+ return diagnosticss
80
+ doneIndexing :: Session [Diagnostic ]
81
+ doneIndexing = satisfyMaybe $ \ case
82
+ FromServerMess SMethod_Progress (TNotificationMessage _ _ (ProgressParams t (preview _workDoneProgressEnd -> Just params))) ->
83
+ case params of
84
+ (WorkDoneProgressEnd _ m) ->
85
+ case m of
86
+ Just message -> bool Nothing (Just [] ) $
87
+ " Finished indexing" `isPrefixOf` message
88
+ _ -> Nothing
89
+ _ -> Nothing
90
+ _ -> Nothing
91
+
61
92
-- | Tests that we can go to the definition of a term in a dependency.
62
93
-- In this case, we are getting the definition of the data
63
94
-- constructor AsyncCancelled.
@@ -68,6 +99,7 @@ dependencyTermTest = testSessionWithExtraFiles "dependency" "gotoDefinition term
68
99
_hieFile <- fileDoneIndexing [" Control" , " Concurrent" , " Async.hie" ]
69
100
defs <- getDefinitions doc (Position 5 20 )
70
101
let expRange = Range (Position 430 22 ) (Position 430 36 )
102
+ diagnostics <- waitForDiagnosticsOrDoneIndexing
71
103
case defs of
72
104
InL (Definition (InR [Location fp actualRange])) ->
73
105
liftIO $ do
@@ -78,6 +110,7 @@ dependencyTermTest = testSessionWithExtraFiles "dependency" "gotoDefinition term
78
110
assertBool " AsyncCancelled found in a module that is not Control.Concurrent Async"
79
111
$ [" Control" , " Concurrent" , " Async.hs" ]
80
112
`isSuffixOf` locationDirectories
113
+ diagnostics @?= []
81
114
actualRange @?= expRange
82
115
wrongLocation ->
83
116
liftIO $
0 commit comments