Skip to content

Commit b478b82

Browse files
authored
Test that GotoHover.hs file compiles in the tests (#572)
* Testsuite: Only run with --test if necessary * Add (failing) test to check GotoHover.hs file compiles * Fix compilation of GotoHover.hs
1 parent bc25ea7 commit b478b82

File tree

3 files changed

+26
-12
lines changed

3 files changed

+26
-12
lines changed

test/data/Bar.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,3 @@
1-
module Bar (Bar) where
1+
module Bar (Bar(..)) where
22

33
data Bar = Bar

test/data/GotoHover.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,10 @@
1+
{-# LANGUAGE OverloadedStrings #-}
12
{- HLINT ignore -}
23
module Testing ( module Testing ) where
34
import Data.Text (Text, pack)
45
import Foo (Bar, foo)
56

67

7-
88
data TypeConstructor = DataConstructor
99
{ fff :: Text
1010
, ggg :: Int }

test/exe/Main.hs

+24-10
Original file line numberDiff line numberDiff line change
@@ -1369,7 +1369,8 @@ findDefinitionAndHoverTests = let
13691369

13701370
mkFindTests tests = testGroup "get"
13711371
[ testGroup "definition" $ mapMaybe fst tests
1372-
, testGroup "hover" $ mapMaybe snd tests ]
1372+
, testGroup "hover" $ mapMaybe snd tests
1373+
, checkFileCompiles sourceFilePath ]
13731374

13741375
test runDef runHover look expect = testM runDef runHover look (return expect)
13751376

@@ -1464,6 +1465,12 @@ findDefinitionAndHoverTests = let
14641465
broken = Just . (`xfail` "known broken")
14651466
no = const Nothing -- don't run this test at all
14661467

1468+
checkFileCompiles :: FilePath -> TestTree
1469+
checkFileCompiles fp =
1470+
testSessionWait ("Does " ++ fp ++ " compile") $
1471+
void (openTestDataDoc fp)
1472+
1473+
14671474
pluginTests :: TestTree
14681475
pluginTests = (`xfail8101` "known broken (#556)")
14691476
$ testSessionWait "plugins" $ do
@@ -2026,8 +2033,8 @@ cradleTests = testGroup "cradle"
20262033

20272034
loadCradleOnlyonce :: TestTree
20282035
loadCradleOnlyonce = testGroup "load cradle only once"
2029-
[ testSession' "implicit" implicit
2030-
, testSession' "direct" direct
2036+
[ testSessionTF "implicit" implicit
2037+
, testSessionTF "direct" direct
20312038
]
20322039
where
20332040
direct dir = do
@@ -2136,7 +2143,10 @@ testSession :: String -> Session () -> TestTree
21362143
testSession name = testCase name . run
21372144

21382145
testSession' :: String -> (FilePath -> Session ()) -> TestTree
2139-
testSession' name = testCase name . run'
2146+
testSession' name = testCase name . run' NoTestFlag
2147+
2148+
testSessionTF :: String -> (FilePath -> Session ()) -> TestTree
2149+
testSessionTF name = testCase name . run' WithTestFlag
21402150

21412151
testSessionWait :: String -> Session () -> TestTree
21422152
testSessionWait name = testSession name .
@@ -2167,13 +2177,16 @@ mkRange :: Int -> Int -> Int -> Int -> Range
21672177
mkRange a b c d = Range (Position a b) (Position c d)
21682178

21692179
run :: Session a -> IO a
2170-
run s = withTempDir $ \dir -> runInDir dir s
2180+
run s = withTempDir $ \dir -> runInDir NoTestFlag dir s
2181+
2182+
run' :: WithTestFlag -> (FilePath -> Session a) -> IO a
2183+
run' tf s = withTempDir $ \dir -> runInDir tf dir (s dir)
21712184

2172-
run' :: (FilePath -> Session a) -> IO a
2173-
run' s = withTempDir $ \dir -> runInDir dir (s dir)
2185+
-- Do we run the LSP executable with --test or not
2186+
data WithTestFlag = WithTestFlag | NoTestFlag deriving (Show, Eq)
21742187

2175-
runInDir :: FilePath -> Session a -> IO a
2176-
runInDir dir s = do
2188+
runInDir :: WithTestFlag -> FilePath -> Session a -> IO a
2189+
runInDir withTestFlag dir s = do
21772190
ghcideExe <- locateGhcideExecutable
21782191

21792192
-- Temporarily hack around https://github.com/mpickering/hie-bios/pull/56
@@ -2186,7 +2199,8 @@ runInDir dir s = do
21862199
createDirectoryIfMissing True $ dir </> takeDirectory f
21872200
copyFile ("test/data" </> f) (dir </> f)
21882201

2189-
let cmd = unwords [ghcideExe, "--lsp", "--test", "--cwd", dir]
2202+
let cmd = unwords ([ghcideExe, "--lsp", "--cwd", dir]
2203+
++ [ "--test" | WithTestFlag == withTestFlag ])
21902204
-- HIE calls getXgdDirectory which assumes that HOME is set.
21912205
-- Only sets HOME if it wasn't already set.
21922206
setEnv "HOME" "/homeless-shelter" False

0 commit comments

Comments
 (0)