Skip to content

Commit 877e75c

Browse files
authored
[Migrate IfaceTests] part of #4173 Migrate ghcide tests to hls test utils and use canonicalizePath path in tmp dir in hls-test-utils (#4201)
* use canonicalizePath path in tmp dir in hls-test-utils * migrate IfaceTests to hls-test-utils
1 parent 0e52d91 commit 877e75c

File tree

4 files changed

+30
-18
lines changed

4 files changed

+30
-18
lines changed

ghcide/test/exe/Config.hs

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -40,5 +40,13 @@ testWithDummyPluginEmpty caseName = testWithDummyPlugin caseName $ mkIdeTestFs [
4040
testWithDummyPluginEmpty' :: String -> (FileSystem -> Session ()) -> TestTree
4141
testWithDummyPluginEmpty' caseName = testWithDummyPlugin' caseName $ mkIdeTestFs []
4242

43+
runWithExtraFiles :: String -> (FileSystem -> Session a) -> IO a
44+
runWithExtraFiles dirName action = do
45+
let vfs = mkIdeTestFs [FS.copyDir dirName]
46+
runWithDummyPlugin' vfs action
47+
48+
testWithExtraFiles :: String -> String -> (FileSystem -> Session ()) -> TestTree
49+
testWithExtraFiles testName dirName action = testCase testName $ runWithExtraFiles dirName action
50+
4351
pattern R :: UInt -> UInt -> UInt -> UInt -> Range
4452
pattern R x y x' y' = Range (Position x y) (Position x' y')

ghcide/test/exe/IfaceTests.hs

Lines changed: 15 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
module IfaceTests (tests) where
22

3+
import Config
34
import Control.Monad.IO.Class (liftIO)
45
import qualified Data.Text as T
56
import Development.IDE.GHC.Util
@@ -17,9 +18,9 @@ import Language.LSP.Test
1718
import System.Directory
1819
import System.FilePath
1920
import System.IO.Extra hiding (withTempDir)
21+
import Test.Hls.FileSystem (toAbsFp)
2022
import Test.Tasty
2123
import Test.Tasty.HUnit
22-
import TestUtils
2324

2425
tests :: TestTree
2526
tests = testGroup "Interface loading tests"
@@ -33,10 +34,10 @@ tests = testGroup "Interface loading tests"
3334

3435
-- | test that TH reevaluates across interfaces
3536
ifaceTHTest :: TestTree
36-
ifaceTHTest = testCase "iface-th-test" $ runWithExtraFiles "TH" $ \dir -> do
37-
let aPath = dir </> "THA.hs"
38-
bPath = dir </> "THB.hs"
39-
cPath = dir </> "THC.hs"
37+
ifaceTHTest = testWithExtraFiles "iface-th-test" "TH" $ \dir -> do
38+
let aPath = dir `toAbsFp` "THA.hs"
39+
bPath = dir `toAbsFp` "THB.hs"
40+
cPath = dir `toAbsFp` "THC.hs"
4041

4142
aSource <- liftIO $ readFileUtf8 aPath -- [TH] a :: ()
4243
_bSource <- liftIO $ readFileUtf8 bPath -- a :: ()
@@ -55,10 +56,10 @@ ifaceTHTest = testCase "iface-th-test" $ runWithExtraFiles "TH" $ \dir -> do
5556
closeDoc cdoc
5657

5758
ifaceErrorTest :: TestTree
58-
ifaceErrorTest = testCase "iface-error-test-1" $ runWithExtraFiles "recomp" $ \dir -> do
59+
ifaceErrorTest = testWithExtraFiles "iface-error-test-1" "recomp" $ \dir -> do
5960
configureCheckProject True
60-
let bPath = dir </> "B.hs"
61-
pPath = dir </> "P.hs"
61+
let bPath = dir `toAbsFp` "B.hs"
62+
pPath = dir `toAbsFp` "P.hs"
6263

6364
bSource <- liftIO $ readFileUtf8 bPath -- y :: Int
6465
pSource <- liftIO $ readFileUtf8 pPath -- bar = x :: Int
@@ -104,9 +105,9 @@ ifaceErrorTest = testCase "iface-error-test-1" $ runWithExtraFiles "recomp" $ \d
104105
expectNoMoreDiagnostics 2
105106

106107
ifaceErrorTest2 :: TestTree
107-
ifaceErrorTest2 = testCase "iface-error-test-2" $ runWithExtraFiles "recomp" $ \dir -> do
108-
let bPath = dir </> "B.hs"
109-
pPath = dir </> "P.hs"
108+
ifaceErrorTest2 = testWithExtraFiles "iface-error-test-2" "recomp" $ \dir -> do
109+
let bPath = dir `toAbsFp` "B.hs"
110+
pPath = dir `toAbsFp` "P.hs"
110111

111112
bSource <- liftIO $ readFileUtf8 bPath -- y :: Int
112113
pSource <- liftIO $ readFileUtf8 pPath -- bar = x :: Int
@@ -138,9 +139,9 @@ ifaceErrorTest2 = testCase "iface-error-test-2" $ runWithExtraFiles "recomp" $ \
138139
expectNoMoreDiagnostics 2
139140

140141
ifaceErrorTest3 :: TestTree
141-
ifaceErrorTest3 = testCase "iface-error-test-3" $ runWithExtraFiles "recomp" $ \dir -> do
142-
let bPath = dir </> "B.hs"
143-
pPath = dir </> "P.hs"
142+
ifaceErrorTest3 = testWithExtraFiles "iface-error-test-3" "recomp" $ \dir -> do
143+
let bPath = dir `toAbsFp` "B.hs"
144+
pPath = dir `toAbsFp` "P.hs"
144145

145146
bSource <- liftIO $ readFileUtf8 bPath -- y :: Int
146147
pSource <- liftIO $ readFileUtf8 pPath -- bar = x :: Int

hls-test-utils/src/Test/Hls.hs

Lines changed: 6 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -106,7 +106,8 @@ import Language.LSP.Protocol.Message
106106
import Language.LSP.Protocol.Types hiding (Null)
107107
import Language.LSP.Test
108108
import Prelude hiding (log)
109-
import System.Directory (createDirectoryIfMissing,
109+
import System.Directory (canonicalizePath,
110+
createDirectoryIfMissing,
110111
getCurrentDirectory,
111112
getTemporaryDirectory,
112113
setCurrentDirectory)
@@ -451,7 +452,10 @@ runSessionWithServerInTmpDirCont plugins conf sessConf caps tree act = withLock
451452
logWith recorder Debug LogCleanup
452453
pure a
453454

454-
runTestInDir $ \tmpDir -> do
455+
runTestInDir $ \tmpDir' -> do
456+
-- we canonicalize the path, so that we do not need to do
457+
-- cannibalization during the test when we compare two paths
458+
tmpDir <- canonicalizePath tmpDir'
455459
logWith recorder Info $ LogTestDir tmpDir
456460
fs <- FS.materialiseVFT tmpDir tree
457461
runSessionWithServer' plugins conf sessConf caps tmpDir (act fs)

hls-test-utils/src/Test/Hls/FileSystem.hs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -128,8 +128,7 @@ materialise rootDir' fileTree testDataDir' = do
128128
--
129129
-- File references in 'virtualFileTree' are resolved relative to the @vftOriginalRoot@.
130130
materialiseVFT :: FilePath -> VirtualFileTree -> IO FileSystem
131-
materialiseVFT root fs =
132-
materialise root (vftTree fs) (vftOriginalRoot fs)
131+
materialiseVFT root fs = materialise root (vftTree fs) (vftOriginalRoot fs)
133132

134133
-- ----------------------------------------------------------------------------
135134
-- Test definition helpers

0 commit comments

Comments
 (0)