Skip to content

Commit 9b90f0a

Browse files
committed
Add test of no diagnostics
1 parent 004568f commit 9b90f0a

File tree

1 file changed

+36
-3
lines changed

1 file changed

+36
-3
lines changed

ghcide/test/exe/Dependency.hs

Lines changed: 36 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -5,23 +5,33 @@ module Dependency where
55

66
import qualified Control.Applicative as Applicative
77
import Control.Applicative.Combinators (skipManyTill)
8+
import Control.Lens (preview, (^.))
89
import Control.Monad.IO.Class (liftIO)
910
import qualified Data.Aeson as A
1011
import Data.Bool (bool)
1112
import Data.List (isSuffixOf)
1213
import Data.Maybe (fromMaybe)
1314
import Data.Proxy (Proxy (..))
15+
import Data.Text (isPrefixOf)
1416
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),
1621
TNotificationMessage (..))
17-
import Language.LSP.Protocol.Types (Definition (..),
22+
import Language.LSP.Protocol.Types (Definition (..), Diagnostic,
1823
Location (..), Position (..),
24+
ProgressParams (..),
1925
Range (..),
26+
WorkDoneProgressEnd (..),
27+
_workDoneProgressEnd,
2028
type (|?) (InL, InR),
2129
uriToFilePath)
2230
import Language.LSP.Test (Session, anyMessage,
2331
customNotification,
24-
getDefinitions, openDoc)
32+
getDefinitions, message,
33+
openDoc, satisfyMaybe,
34+
waitForDiagnostics)
2535
import System.FilePath (splitDirectories, (<.>),
2636
(</>))
2737
import Test.Tasty (TestTree, testGroup)
@@ -58,6 +68,27 @@ fileDoneIndexing fpSuffix =
5868
fpSuffix `isSuffixOf` fpDirs
5969
other -> error $ "Failed to parse ghcide/reference/ready file: " <> show other
6070

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+
6192
-- | Tests that we can go to the definition of a term in a dependency.
6293
-- In this case, we are getting the definition of the data
6394
-- constructor AsyncCancelled.
@@ -68,6 +99,7 @@ dependencyTermTest = testSessionWithExtraFiles "dependency" "gotoDefinition term
6899
_hieFile <- fileDoneIndexing ["Control", "Concurrent", "Async.hie"]
69100
defs <- getDefinitions doc (Position 5 20)
70101
let expRange = Range (Position 430 22) (Position 430 36)
102+
diagnostics <- waitForDiagnosticsOrDoneIndexing
71103
case defs of
72104
InL (Definition (InR [Location fp actualRange])) ->
73105
liftIO $ do
@@ -78,6 +110,7 @@ dependencyTermTest = testSessionWithExtraFiles "dependency" "gotoDefinition term
78110
assertBool "AsyncCancelled found in a module that is not Control.Concurrent Async"
79111
$ ["Control", "Concurrent", "Async.hs"]
80112
`isSuffixOf` locationDirectories
113+
diagnostics @?= []
81114
actualRange @?= expRange
82115
wrongLocation ->
83116
liftIO $

0 commit comments

Comments
 (0)