Skip to content

Commit e2d17a7

Browse files
committed
Add goto dependency definition test
1 parent e4efd0d commit e2d17a7

File tree

6 files changed

+85
-0
lines changed

6 files changed

+85
-0
lines changed

ghcide/ghcide.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -418,6 +418,7 @@ test-suite ghcide-tests
418418
ReferenceTests
419419
GarbageCollectionTests
420420
OpenCloseTest
421+
Dependency
421422
default-extensions:
422423
BangPatterns
423424
DeriveFunctor
Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,6 @@
1+
module Dependency where
2+
3+
import Control.Concurrent.Async (AsyncCancelled(..))
4+
5+
asyncCancelled :: AsyncCancelled
6+
asyncCancelled = AsyncCancelled
Lines changed: 11 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,11 @@
1+
name: dependency
2+
version: 0.1.0.0
3+
cabal-version: 2.0
4+
build-type: Simple
5+
6+
library
7+
exposed-modules: Dependency
8+
default-language: Haskell2010
9+
build-depends: base
10+
, async == 2.2.4
11+
ghc-options: -fwrite-ide-info

ghcide/test/data/dependency/hie.yaml

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,2 @@
1+
cradle:
2+
cabal:

ghcide/test/exe/Dependency.hs

Lines changed: 63 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,63 @@
1+
{-# LANGUAGE DataKinds #-}
2+
{-# LANGUAGE ExplicitNamespaces #-}
3+
{-# LANGUAGE GADTs #-}
4+
module Dependency where
5+
6+
import qualified Data.Aeson as A
7+
import Data.Bool (bool)
8+
import Data.List (isSuffixOf)
9+
import Data.Proxy (Proxy(..))
10+
import qualified Control.Applicative as Applicative
11+
import Control.Applicative.Combinators (skipManyTill)
12+
import Control.Monad.IO.Class (liftIO)
13+
import Language.LSP.Protocol.Message (TCustomMessage(NotMess), TNotificationMessage(..))
14+
import Language.LSP.Protocol.Types (type (|?) (InL, InR), Definition(..), Location(..), Position(..), Range(..), uriToFilePath)
15+
import Language.LSP.Test (Session, anyMessage, customNotification, getDefinitions, openDoc)
16+
import System.FilePath ((</>), (<.>), splitDirectories)
17+
import Test.Tasty (TestTree, testGroup)
18+
import Test.Tasty.HUnit ((@?=), assertBool, assertFailure)
19+
import TestUtils (testSessionWithExtraFiles)
20+
21+
tests :: TestTree
22+
tests =
23+
testGroup "gotoDefinition for dependencies"
24+
[ dependencyTest
25+
]
26+
where
27+
dependencyTest :: TestTree
28+
dependencyTest = testSessionWithExtraFiles "dependency" "gotoDefinition in async" $
29+
\dir -> do
30+
doc <- openDoc (dir </> "Dependency" <.> "hs") "haskell"
31+
_hieFile <- fileDoneIndexing ["Control", "Concurrent", "Async.hie"]
32+
defs <- getDefinitions doc (Position 5 20)
33+
let expRange = Range (Position 430 22) (Position 430 36)
34+
case defs of
35+
InL (Definition (InR [Location fp actualRange])) ->
36+
liftIO $ do
37+
let locationDirectories :: [String]
38+
locationDirectories =
39+
maybe [] splitDirectories $
40+
uriToFilePath fp
41+
assertBool "AsyncCancelled found in a module that is not Control.Concurrent Async"
42+
$ ["Control", "Concurrent", "Async.hs"]
43+
`isSuffixOf` locationDirectories
44+
actualRange @?= expRange
45+
wrongLocation ->
46+
liftIO $
47+
assertFailure $ "Wrong location for AsyncCancelled: "
48+
++ show wrongLocation
49+
fileDoneIndexing :: [String] -> Session FilePath
50+
fileDoneIndexing fpSuffix =
51+
skipManyTill anyMessage indexedFile
52+
where
53+
indexedFile :: Session FilePath
54+
indexedFile = do
55+
NotMess TNotificationMessage{_params} <-
56+
customNotification (Proxy @"ghcide/reference/ready")
57+
case A.fromJSON _params of
58+
A.Success fp -> do
59+
let fpDirs :: [String]
60+
fpDirs = splitDirectories fp
61+
bool Applicative.empty (pure fp) $
62+
fpSuffix `isSuffixOf` fpDirs
63+
other -> error $ "Failed to parse ghcide/reference/ready file: " <> show other

ghcide/test/exe/Main.hs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -76,6 +76,7 @@ import ClientSettingsTests
7676
import ReferenceTests
7777
import GarbageCollectionTests
7878
import ExceptionTests
79+
import Dependency
7980

8081
main :: IO ()
8182
main = do
@@ -124,4 +125,5 @@ main = do
124125
, GarbageCollectionTests.tests
125126
, HieDbRetry.tests
126127
, ExceptionTests.tests recorder logger
128+
, Dependency.tests
127129
]

0 commit comments

Comments
 (0)