Skip to content

Commit 5325556

Browse files
committed
Add dependency where clause test (failing)
1 parent 972767c commit 5325556

File tree

5 files changed

+70
-0
lines changed

5 files changed

+70
-0
lines changed
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 Data.Scientific (Scientific(base10Exponent))
4+
5+
b :: Scientific -> Int
6+
b = base10Exponent
Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,3 @@
1+
packages: .
2+
package *
3+
ghc-options: -fwrite-ide-info
Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,10 @@
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+
, scientific == 0.3.7.0
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: 49 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -25,6 +25,7 @@ import Language.LSP.Test (Session, anyMessage,
2525
import System.FilePath (splitDirectories, (<.>),
2626
(</>))
2727
import Test.Tasty (TestTree, testGroup)
28+
import Test.Tasty.ExpectedFailure (expectFailBecause)
2829
import Test.Tasty.HUnit (assertBool, assertFailure,
2930
(@?=))
3031
import TestUtils (testSessionWithExtraFiles, knownBrokenForGhcVersions)
@@ -37,6 +38,7 @@ tests =
3738
, transitiveDependencyTest
3839
, autogenDependencyTest
3940
, bootDependencyTest
41+
, whereClauseDependencyTest
4042
]
4143

4244
fileDoneIndexing :: [String] -> Session FilePath
@@ -235,3 +237,50 @@ bootDependencyTest = knownBrokenForGhcVersions [GHC810, GHC90, GHC92, GHC94, GHC
235237
liftIO $
236238
assertFailure $ "Wrong location for empty: "
237239
++ show wrongLocation
240+
241+
-- Testing that we can go to a definition in a where clause in a dependency.
242+
-- This currently fails, but it is unclear why.
243+
whereClauseDependencyTest :: TestTree
244+
whereClauseDependencyTest = expectFailBecause "TODO: figure out why where clauses in dependencies are not indexed" $
245+
testSessionWithExtraFiles "dependency-where" "goto where clause definition in dependency" $
246+
\dir -> do
247+
localDoc <- openDoc (dir </> "Dependency" <.> "hs") "haskell"
248+
_hieFile <- fileDoneIndexing ["Data", "Scientific.hie"]
249+
scientificDefs <- getDefinitions localDoc (Position 5 5)
250+
scientificFile <- case scientificDefs of
251+
InL (Definition (InR [Location uri _actualRange])) ->
252+
liftIO $ do
253+
let fp :: FilePath
254+
fp = fromMaybe "" $ uriToFilePath uri
255+
locationDirectories :: [String]
256+
locationDirectories = splitDirectories fp
257+
assertBool "base10Exponent found in a module that is not Data.Scientific"
258+
$ ["Data", "Scientific.hs"]
259+
`isSuffixOf` locationDirectories
260+
pure fp
261+
wrongLocation ->
262+
liftIO $
263+
assertFailure $ "Wrong location for base10Exponent: "
264+
++ show wrongLocation
265+
scientificDoc <- openDoc scientificFile "haskell"
266+
-- Where longDiv is referenced in the function body
267+
-- of unsafeFromRational in Data.Scientific
268+
longDivDefs <- getDefinitions scientificDoc (Position 367 33)
269+
-- The location of the definition of longDiv in
270+
-- the where clause of unsafeFromRational
271+
let expRange = Range (Position 371 4) (Position 376 55)
272+
case longDivDefs of
273+
InL (Definition (InR [Location uri actualRange])) ->
274+
liftIO $ do
275+
let locationDirectories :: [String]
276+
locationDirectories =
277+
maybe [] splitDirectories $
278+
uriToFilePath uri
279+
assertBool "longDiv found in a module that is not Data.Scientific"
280+
$ ["Data", "Scientific.hs"]
281+
`isSuffixOf` locationDirectories
282+
actualRange @?= expRange
283+
wrongLocation ->
284+
liftIO $
285+
assertFailure $ "Wrong location for longDiv: "
286+
++ show wrongLocation

0 commit comments

Comments
 (0)