Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension


Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
7 changes: 7 additions & 0 deletions .github/actions/setup-build/action.yml
Original file line number Diff line number Diff line change
Expand Up @@ -44,6 +44,13 @@ runs:
echo "CABAL_PKGS_DIR=C:\\cabal\\packages" >> $GITHUB_ENV
shell: bash

- if: inputs.os == 'Windows'
name: (Windows) Platform config (root test directory)
run: |
mkdir C:\\hls-tests
echo "HLS_TEST_ROOTDIR=C:\\hls-tests" >> $GITHUB_ENV
shell: bash

- if: ( inputs.os == 'Linux' ) || ( inputs.os == 'macOS' )
name: (Linux,macOS) Platform config
run: |
Expand Down
3 changes: 1 addition & 2 deletions .github/workflows/test.yml
Original file line number Diff line number Diff line change
Expand Up @@ -48,8 +48,7 @@ jobs:
uses: fkirc/[email protected]
with:
cancel_others: false
paths_ignore: '[ "hls-test-utils/**"
, "plugins/**"
paths_ignore: '[ "plugins/**"
, "src/**"
, "exe/**"
, "test/**"
Expand Down
37 changes: 18 additions & 19 deletions ghcide-test/exe/BootTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,25 +27,24 @@ tests = testGroup "boot"
let cPath = dir </> "C.hs"
cSource <- liftIO $ readFileUtf8 cPath
-- Dirty the cache
liftIO $ runInDir dir $ do
cDoc <- createDoc cPath "haskell" cSource
-- We send a hover request then wait for either the hover response or
-- `ghcide/reference/ready` notification.
-- Once we receive one of the above, we wait for the other that we
-- haven't received yet.
-- If we don't wait for the `ready` notification it is possible
-- that the `getDefinitions` request/response in the outer ghcide
-- session will find no definitions.
let hoverParams = HoverParams cDoc (Position 4 3) Nothing
hoverRequestId <- sendRequest SMethod_TextDocumentHover hoverParams
let parseReadyMessage = isReferenceReady cPath
let parseHoverResponse = responseForId SMethod_TextDocumentHover hoverRequestId
hoverResponseOrReadyMessage <- skipManyTill anyMessage ((Left <$> parseHoverResponse) <|> (Right <$> parseReadyMessage))
_ <- skipManyTill anyMessage $
case hoverResponseOrReadyMessage of
Left _ -> void parseReadyMessage
Right _ -> void parseHoverResponse
closeDoc cDoc
cDoc <- createDoc cPath "haskell" cSource
-- We send a hover request then wait for either the hover response or
-- `ghcide/reference/ready` notification.
-- Once we receive one of the above, we wait for the other that we
-- haven't received yet.
-- If we don't wait for the `ready` notification it is possible
-- that the `getDefinitions` request/response in the outer ghcide
-- session will find no definitions.
let hoverParams = HoverParams cDoc (Position 4 3) Nothing
hoverRequestId <- sendRequest SMethod_TextDocumentHover hoverParams
let parseReadyMessage = isReferenceReady cPath
let parseHoverResponse = responseForId SMethod_TextDocumentHover hoverRequestId
hoverResponseOrReadyMessage <- skipManyTill anyMessage ((Left <$> parseHoverResponse) <|> (Right <$> parseReadyMessage))
_ <- skipManyTill anyMessage $
case hoverResponseOrReadyMessage of
Left _ -> void parseReadyMessage
Right _ -> void parseHoverResponse
closeDoc cDoc
cdoc <- createDoc cPath "haskell" cSource
locs <- getDefinitions cdoc (Position 7 4)
let floc = mkR 9 0 9 1
Expand Down
11 changes: 4 additions & 7 deletions ghcide-test/exe/CradleTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@

module CradleTests (tests) where

import Config (checkDefs, mkL, runInDir,
import Config (checkDefs, mkL,
runWithExtraFiles,
testWithDummyPluginEmpty')
import Control.Applicative.Combinators
Expand Down Expand Up @@ -180,12 +180,9 @@ simpleMultiDefTest variant = ignoreForWindows $ testCase testName $
runWithExtraFiles variant $ \dir -> do
let aPath = dir </> "a/A.hs"
bPath = dir </> "b/B.hs"
adoc <- liftIO $ runInDir dir $ do
aSource <- liftIO $ readFileUtf8 aPath
adoc <- createDoc aPath "haskell" aSource
skipManyTill anyMessage $ isReferenceReady aPath
closeDoc adoc
pure adoc
adoc <- openDoc aPath "haskell"
skipManyTill anyMessage $ isReferenceReady aPath
closeDoc adoc
bSource <- liftIO $ readFileUtf8 bPath
bdoc <- createDoc bPath "haskell" bSource
locs <- getDefinitions bdoc (Position 2 7)
Expand Down
2 changes: 1 addition & 1 deletion ghcide-test/exe/FindDefinitionAndHoverTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -188,7 +188,7 @@ tests = let
cccL17 = Position 17 16 ; docLink = [ExpectHoverTextRegex "\\*Defined in 'GHC.Types'\\* \\*\\(ghc-prim-[0-9.]+\\)\\*\n\n"]
imported = Position 56 13 ; importedSig = getDocUri "Foo.hs" >>= \foo -> return [ExpectHoverText ["foo", "Foo", "Haddock"], mkL foo 5 0 5 3]
reexported = Position 55 14
reexportedSig = getDocUri "Bar.hs" >>= \bar -> return [ExpectHoverText ["Bar", "Bar", "Haddock"], if ghcVersion < GHC910 || not isWindows then mkL bar 3 5 3 8 else mkL bar 3 0 3 14]
reexportedSig = getDocUri "Bar.hs" >>= \bar -> return [ExpectHoverText ["Bar", "Bar", "Haddock"], mkL bar 3 0 3 14]
thLocL57 = Position 59 10 ; thLoc = [ExpectHoverText ["Identity"]]
cmtL68 = Position 67 0 ; lackOfdEq = [ExpectHoverExcludeText ["$dEq"]]
import310 = Position 3 10; pkgTxt = [ExpectHoverText ["Data.Text\n\ntext-"]]
Expand Down
102 changes: 78 additions & 24 deletions hls-test-utils/src/Test/Hls.hs
Original file line number Diff line number Diff line change
Expand Up @@ -507,32 +507,73 @@ runSessionWithServerInTmpDir config plugin tree act =
{testLspConfig=config, testPluginDescriptor = plugin, testDirLocation=Right tree}
(const act)

runWithLockInTempDir :: VirtualFileTree -> (FileSystem -> IO a) -> IO a
runWithLockInTempDir tree act = withLock lockForTempDirs $ do
-- | Same as 'withTemporaryDataAndCacheDirectory', but materialises the given
-- 'VirtualFileTree' in the temporary directory.
withVfsTestDataDirectory :: VirtualFileTree -> (FileSystem -> IO a) -> IO a
withVfsTestDataDirectory tree act = do
withTemporaryDataAndCacheDirectory $ \tmpRoot -> do
fs <- FS.materialiseVFT tmpRoot tree
act fs

-- | Run an action in a temporary directory.
-- Sets the 'XDG_CACHE_HOME' environment variable to a temporary directory as well.
--
-- This sets up a temporary directory for HLS tests to run.
-- Typically, HLS tests copy their test data into the directory and then launch
-- the HLS session in that directory.
-- This makes sure that the tests are run in isolation, which is good for correctness
-- but also important to have fast tests.
--
-- For improved isolation, we also make sure the 'XDG_CACHE_HOME' environment
-- variable points to a temporary directory. So, we never share interface files
-- or the 'hiedb' across tests.
withTemporaryDataAndCacheDirectory :: (FilePath -> IO a) -> IO a
withTemporaryDataAndCacheDirectory act = withLock lockForTempDirs $ do
testRoot <- setupTestEnvironment
helperRecorder <- hlsHelperTestRecorder
-- Do not clean up the temporary directory if this variable is set to anything but '0'.
-- Aids debugging.
cleanupTempDir <- lookupEnv "HLS_TEST_HARNESS_NO_TESTDIR_CLEANUP"
let runTestInDir action = case cleanupTempDir of
Just val | val /= "0" -> do
(tempDir, _) <- newTempDirWithin testRoot
a <- action tempDir
(tempDir, cacheHome, _) <- setupTemporaryTestDirectories testRoot
a <- withTempCacheHome cacheHome (action tempDir)
logWith helperRecorder Debug LogNoCleanup
pure a

_ -> do
(tempDir, cleanup) <- newTempDirWithin testRoot
a <- action tempDir `finally` cleanup
(tempDir, cacheHome, cleanup) <- setupTemporaryTestDirectories testRoot
a <- withTempCacheHome cacheHome (action tempDir) `finally` cleanup
logWith helperRecorder Debug LogCleanup
pure a
runTestInDir $ \tmpDir' -> do
-- we canonicalize the path, so that we do not need to do
-- cannibalization during the test when we compare two paths
-- canonicalization during the test when we compare two paths
tmpDir <- canonicalizePath tmpDir'
logWith helperRecorder Info $ LogTestDir tmpDir
fs <- FS.materialiseVFT tmpDir tree
act fs
act tmpDir
where
cache_home_var = "XDG_CACHE_HOME"
-- Set the dir for "XDG_CACHE_HOME".
-- When the operation finished, make sure the old value is restored.
withTempCacheHome tempCacheHomeDir act =
bracket
(do
old_cache_home <- lookupEnv cache_home_var
setEnv cache_home_var tempCacheHomeDir
pure old_cache_home)
(\old_cache_home ->
maybe (pure ()) (setEnv cache_home_var) old_cache_home
)
(\_ -> act)

-- Set up a temporary directory for the test files and one for the 'XDG_CACHE_HOME'.
-- The 'XDG_CACHE_HOME' is important for independent test runs, i.e. completely empty
-- caches.
setupTemporaryTestDirectories testRoot = do
(tempTestCaseDir, cleanup1) <- newTempDirWithin testRoot
(tempCacheHomeDir, cleanup2) <- newTempDirWithin testRoot
pure (tempTestCaseDir, tempCacheHomeDir, cleanup1 >> cleanup2)

runSessionWithServer :: Pretty b => Config -> PluginTestDescriptor b -> FilePath -> Session a -> IO a
runSessionWithServer config plugin fp act =
Expand Down Expand Up @@ -565,18 +606,18 @@ instance Default (TestConfig b) where
-- It returns the root to the testing directory that tests should use.
-- This directory is not fully cleaned between reruns.
-- However, it is totally safe to delete the directory between runs.
--
-- Additionally, this overwrites the 'XDG_CACHE_HOME' variable to isolate
-- the tests from existing caches. 'hie-bios' and 'ghcide' honour the
-- 'XDG_CACHE_HOME' environment variable and generate their caches there.
setupTestEnvironment :: IO FilePath
setupTestEnvironment = do
tmpDirRoot <- getTemporaryDirectory
let testRoot = tmpDirRoot </> "hls-test-root"
testCacheDir = testRoot </> ".cache"
createDirectoryIfMissing True testCacheDir
setEnv "XDG_CACHE_HOME" testCacheDir
pure testRoot
mRootDir <- lookupEnv "HLS_TEST_ROOTDIR"
case mRootDir of
Nothing -> do
tmpDirRoot <- getTemporaryDirectory
let testRoot = tmpDirRoot </> "hls-test-root"
createDirectoryIfMissing True testRoot
pure testRoot
Just rootDir -> do
createDirectoryIfMissing True rootDir
pure rootDir

goldenWithHaskellDocFormatter
:: Pretty b
Expand Down Expand Up @@ -692,7 +733,6 @@ lockForTempDirs = unsafePerformIO newLock
data TestConfig b = TestConfig
{
testDirLocation :: Either FilePath VirtualFileTree
-- ^ Client capabilities
-- ^ The file tree to use for the test, either a directory or a virtual file tree
-- if using a virtual file tree,
-- Creates a temporary directory, and materializes the VirtualFileTree
Expand Down Expand Up @@ -747,8 +787,20 @@ wrapClientLogger logger = do
return (lspLogRecorder <> logger, cb1)

-- | Host a server, and run a test session on it.
-- For setting custom timeout, set the environment variable 'LSP_TIMEOUT'
-- * LSP_TIMEOUT=10 cabal test
--
-- Environment variables are used to influence logging verbosity, test cleanup and test execution:
--
-- * @LSP_TIMEOUT@: Set a specific test timeout in seconds.
-- * @LSP_TEST_LOG_MESSAGES@: Log the LSP messages between the client and server.
-- * @LSP_TEST_LOG_STDERR@: Log the stderr of the server to the stderr of this process.
-- * @HLS_TEST_HARNESS_STDERR@: Log test setup messages.
--
-- Test specific environment variables:
--
-- * @HLS_TEST_PLUGIN_LOG_STDERR@: Log all messages of the hls plugin under test to stderr.
-- * @HLS_TEST_LOG_STDERR@: Log all HLS messages to stderr.
-- * @HLS_TEST_HARNESS_NO_TESTDIR_CLEANUP@: Don't remove the test directories after test execution.
--
-- For more detail of the test configuration, see 'TestConfig'
runSessionWithTestConfig :: Pretty b => TestConfig b -> (FilePath -> Session a) -> IO a
runSessionWithTestConfig TestConfig{..} session =
Expand Down Expand Up @@ -792,8 +844,10 @@ runSessionWithTestConfig TestConfig{..} session =
else f
runSessionInVFS (Left testConfigRoot) act = do
root <- makeAbsolute testConfigRoot
act root
runSessionInVFS (Right vfs) act = runWithLockInTempDir vfs $ \fs -> act (fsRoot fs)
withTemporaryDataAndCacheDirectory (const $ act root)
runSessionInVFS (Right vfs) act =
withVfsTestDataDirectory vfs $ \fs -> do
act (fsRoot fs)
testingArgs prjRoot recorderIde plugins =
let
arguments@Arguments{ argsHlsPlugins, argsIdeOptions, argsLspOptions } = defaultArguments (cmapWithPrio LogIDEMain recorderIde) prjRoot plugins
Expand Down
43 changes: 21 additions & 22 deletions plugins/hls-cabal-plugin/test/CabalAdd.hs
Original file line number Diff line number Diff line change
Expand Up @@ -83,30 +83,29 @@ cabalAddDependencyTests :: TestTree
cabalAddDependencyTests =
testGroup
"Add dependency"
[ runHaskellTestCaseSession "Add to executable" ("cabal-add-testdata" </> "cabal-add-exe")
(generateAddDependencyTestSession "cabal-add-exe.cabal" ("src" </> "Main.hs") "split" [253])
, runHaskellTestCaseSession "Add to library" ("cabal-add-testdata" </> "cabal-add-lib")
(generateAddDependencyTestSession "cabal-add-lib.cabal" ("src" </> "MyLib.hs") "split" [348])
, runHaskellTestCaseSession "Add to testsuite" ("cabal-add-testdata" </> "cabal-add-tests")
(generateAddDependencyTestSession "cabal-add-tests.cabal" ("test" </> "Main.hs") "split" [478])
, runHaskellTestCaseSession "Add to testsuite with PackageImports" ("cabal-add-testdata" </> "cabal-add-tests")
(generateAddDependencyTestSession "cabal-add-tests.cabal" ("test" </> "MainPackageImports.hs") "split" [731])
, runHaskellTestCaseSession "Add to benchmark" ("cabal-add-testdata" </> "cabal-add-bench")
(generateAddDependencyTestSession "cabal-add-bench.cabal" ("bench" </> "Main.hs") "split" [403])
[ runHaskellTestCaseSession "Add to executable" ("cabal-add-testdata" </> "exe")
(generateAddDependencyTestSession "exe.cabal" ("src" </> "Main.hs") "split" [253])
, runHaskellTestCaseSession "Add to library" ("cabal-add-testdata" </> "lib")
(generateAddDependencyTestSession "lib.cabal" ("src" </> "MyLib.hs") "split" [348])
, runHaskellTestCaseSession "Add to testsuite" ("cabal-add-testdata" </> "tests")
(generateAddDependencyTestSession "tests.cabal" ("test" </> "Main.hs") "split" [478])
, runHaskellTestCaseSession "Add to testsuite with PackageImports" ("cabal-add-testdata" </> "tests")
(generateAddDependencyTestSession "tests.cabal" ("test" </> "MainPackageImports.hs") "split" [731])
, runHaskellTestCaseSession "Add to benchmark" ("cabal-add-testdata" </> "bench")
(generateAddDependencyTestSession "bench.cabal" ("bench" </> "Main.hs") "split" [403])

, runHaskellTestCaseSession "Add to executable, multiple targets" ("cabal-add-testdata" </> "cabal-add-multitarget")
(generateAddDependencyTestSession "cabal-add-multitarget.cabal" ("src" </> "Main.hs") "split" [269])
, runHaskellTestCaseSession "Add to library, multiple targets" ("cabal-add-testdata" </> "cabal-add-multitarget")
(generateAddDependencyTestSession "cabal-add-multitarget.cabal" ("lib" </> "MyLib.hs") "split" [413])
, runHaskellTestCaseSession "Add to internal library, multiple targets" ("cabal-add-testdata" </> "cabal-add-multitarget")
(generateAddDependencyTestSession "cabal-add-multitarget.cabal" ("lib" </> "InternalLib.hs") "split" [413])
, runHaskellTestCaseSession "Add to testsuite, multiple targets" ("cabal-add-testdata" </> "cabal-add-multitarget")
(generateAddDependencyTestSession "cabal-add-multitarget.cabal" ("test" </> "Main.hs") "split" [655])
, runHaskellTestCaseSession "Add to benchmark, multiple targets" ("cabal-add-testdata" </> "cabal-add-multitarget")
(generateAddDependencyTestSession "cabal-add-multitarget.cabal" ("bench" </> "Main.hs") "split" [776])
, runHaskellTestCaseSession "Add to executable, multiple targets" ("cabal-add-testdata" </> "multitarget")
(generateAddDependencyTestSession "multitarget.cabal" ("src" </> "Main.hs") "split" [269])
, runHaskellTestCaseSession "Add to library, multiple targets" ("cabal-add-testdata" </> "multitarget")
(generateAddDependencyTestSession "multitarget.cabal" ("lib" </> "MyLib.hs") "split" [413])
, runHaskellTestCaseSession "Add to internal library, multiple targets" ("cabal-add-testdata" </> "multitarget")
(generateAddDependencyTestSession "multitarget.cabal" ("lib" </> "InternalLib.hs") "split" [413])
, runHaskellTestCaseSession "Add to testsuite, multiple targets" ("cabal-add-testdata" </> "multitarget")
(generateAddDependencyTestSession "multitarget.cabal" ("test" </> "Main.hs") "split" [655])
, runHaskellTestCaseSession "Add to benchmark, multiple targets" ("cabal-add-testdata" </> "multitarget")
(generateAddDependencyTestSession "multitarget.cabal" ("bench" </> "Main.hs") "split" [776])


, runHaskellTestCaseSession "Guard against HPack" ("cabal-add-testdata" </> "cabal-add-packageYaml")
, runHaskellTestCaseSession "Guard against HPack" ("cabal-add-testdata" </> "packageYaml")
(generatePackageYAMLTestSession ("src" </> "Main.hs"))

, testHiddenPackageSuggestions "Check CabalAdd's parser, no version"
Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
packages: ./

This file was deleted.

Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
packages: ./
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
cradle:
cabal:
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
packages: ./
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
cradle:
cabal:
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
packages: ./
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
cradle:
cabal:
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
packages: ./
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
cradle:
cabal:
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
packages: ./
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
cradle:
cabal:
Loading