Skip to content

Commit eb05e49

Browse files
committed
Add augogen dependency test
1 parent 185a63b commit eb05e49

File tree

5 files changed

+76
-1
lines changed

5 files changed

+76
-1
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 Language.Haskell.Stylish (Step, tabs)
4+
5+
t :: Int -> Step
6+
t = tabs
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-autogen
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+
, stylish-haskell == 0.14.5.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: 55 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -11,6 +11,7 @@ import Data.Bool (bool)
1111
import Data.List (isSuffixOf)
1212
import Data.Maybe (fromMaybe)
1313
import Data.Proxy (Proxy (..))
14+
import Development.IDE.GHC.Compat (GhcVersion (..))
1415
import Language.LSP.Protocol.Message (TCustomMessage (NotMess),
1516
TNotificationMessage (..))
1617
import Language.LSP.Protocol.Types (Definition (..),
@@ -26,13 +27,14 @@ import System.FilePath (splitDirectories, (<.>),
2627
import Test.Tasty (TestTree, testGroup)
2728
import Test.Tasty.HUnit (assertBool, assertFailure,
2829
(@?=))
29-
import TestUtils (testSessionWithExtraFiles)
30+
import TestUtils (testSessionWithExtraFiles, knownBrokenForGhcVersions)
3031

3132
tests :: TestTree
3233
tests =
3334
testGroup "gotoDefinition for dependencies"
3435
[ dependencyTest
3536
, transitiveDependencyTest
37+
, autogenDependencyTest
3638
]
3739

3840
fileDoneIndexing :: [String] -> Session FilePath
@@ -119,3 +121,55 @@ transitiveDependencyTest = testSessionWithExtraFiles "dependency" "goto transiti
119121
liftIO $
120122
assertFailure $ "Wrong location for Hashable: "
121123
++ show wrongLocation
124+
125+
-- Testing that we can go to a definition in an autogen module of a
126+
-- dependency. Stylish haskell is a package that has an autogen module,
127+
-- but it doesn't seem to build with ghc 9.0 or earlier. Suggestions on
128+
-- another package we could use for this test are welcome! This test
129+
-- doesn't go directly to the fuction in the autogen module because
130+
-- it is a hidden module, so we can't import that function directly
131+
-- in our project. However, hidden modules are also indexed, so we
132+
-- can go to a definition in a module that imports the autogen module
133+
-- and goto the autogen module from there.
134+
autogenDependencyTest :: TestTree
135+
autogenDependencyTest = knownBrokenForGhcVersions [GHC810, GHC90] "stylish-haskell does not build with older GHC versions" $
136+
testSessionWithExtraFiles "dependency-autogen" "goto autogen module in dependency" $
137+
\dir -> do
138+
localDoc <- openDoc (dir </> "Dependency" <.> "hs") "haskell"
139+
_hieFile <- fileDoneIndexing ["Paths_stylish_haskell.hie"]
140+
stylishDefs <- getDefinitions localDoc (Position 5 5)
141+
stylishFile <- case stylishDefs of
142+
InL (Definition (InR [Location uri _actualRange])) ->
143+
liftIO $ do
144+
let fp :: FilePath
145+
fp = fromMaybe "" $ uriToFilePath uri
146+
locationDirectories :: [String]
147+
locationDirectories = splitDirectories fp
148+
assertBool "tags found in a module that is not Language.Haskell.Stylish"
149+
$ ["Language", "Haskell", "Stylish.hs"]
150+
`isSuffixOf` locationDirectories
151+
pure fp
152+
wrongLocation ->
153+
liftIO $
154+
assertFailure $ "Wrong location for AsyncCancelled: "
155+
++ show wrongLocation
156+
stylishDoc <- openDoc stylishFile "haskell"
157+
pathsDefs <- getDefinitions stylishDoc (Position 19 8)
158+
-- The location of the definition of version in
159+
-- Paths_stylish_haskell
160+
let expRange = Range (Position 35 0) (Position 35 7)
161+
case pathsDefs of
162+
InL (Definition (InR [Location uri actualRange])) ->
163+
liftIO $ do
164+
let locationDirectories :: [String]
165+
locationDirectories =
166+
maybe [] splitDirectories $
167+
uriToFilePath uri
168+
assertBool "version found in a module that is not Paths_stylish_haskell"
169+
$ ["Paths_stylish_haskell.hs"]
170+
`isSuffixOf` locationDirectories
171+
actualRange @?= expRange
172+
wrongLocation ->
173+
liftIO $
174+
assertFailure $ "Wrong location for version: "
175+
++ show wrongLocation

0 commit comments

Comments
 (0)