Skip to content

Commit fe1f476

Browse files
committed
Attemp to fix failures in hls-rename-plugin test suite
The tests run all in parallel on the same workspace, and most of the modules have the same module name Main. Result: parallel writes to the same .hie files in the local tmp folder that lead to IO errors in Windows
1 parent c3ce8a4 commit fe1f476

File tree

2 files changed

+58
-30
lines changed

2 files changed

+58
-30
lines changed

hls-test-utils/hls-test-utils.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -50,6 +50,7 @@ library
5050
, lsp ^>=1.2
5151
, lsp-test ^>=0.14
5252
, lsp-types >=1.2 && <1.4
53+
, shake
5354
, tasty
5455
, tasty-expected-failure
5556
, tasty-golden

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

Lines changed: 57 additions & 30 deletions
Original file line numberDiff line numberDiff line change
@@ -27,45 +27,50 @@ module Test.Hls
2727
where
2828

2929
import Control.Applicative.Combinators
30-
import Control.Concurrent.Async (async, cancel, wait)
30+
import Control.Concurrent.Async (async, cancel, wait)
3131
import Control.Concurrent.Extra
3232
import Control.Exception.Base
33-
import Control.Monad (unless, void)
33+
import Control.Monad (unless, void)
3434
import Control.Monad.IO.Class
35-
import Data.Aeson (Value (Null), toJSON)
36-
import Data.ByteString.Lazy (ByteString)
37-
import Data.Default (def)
38-
import qualified Data.Text as T
39-
import qualified Data.Text.Lazy as TL
40-
import qualified Data.Text.Lazy.Encoding as TL
41-
import Development.IDE (IdeState, hDuplicateTo',
42-
noLogging)
43-
import Development.IDE.Graph (ShakeOptions (shakeThreads))
35+
import Data.Aeson (Value (Null), toJSON)
36+
import Data.ByteString.Lazy (ByteString)
37+
import Data.Default (def)
38+
import Data.Foldable (for_)
39+
import qualified Data.Text as T
40+
import qualified Data.Text.Lazy as TL
41+
import qualified Data.Text.Lazy.Encoding as TL
42+
import Development.IDE (IdeState, hDuplicateTo',
43+
noLogging)
44+
import Development.IDE.Graph (ShakeOptions (shakeThreads))
4445
import Development.IDE.Main
45-
import qualified Development.IDE.Main as Ghcide
46-
import qualified Development.IDE.Plugin.HLS.GhcIde as Ghcide
47-
import Development.IDE.Plugin.Test (TestRequest (WaitForShakeQueue))
46+
import qualified Development.IDE.Main as Ghcide
47+
import Development.IDE.Plugin.Test (TestRequest (WaitForShakeQueue))
4848
import Development.IDE.Types.Options
49+
import Development.Shake (getDirectoryFilesIO)
4950
import GHC.IO.Handle
50-
import Ide.Plugin.Config (Config, formattingProvider)
51-
import Ide.PluginUtils (idePluginsToPluginDesc,
52-
pluginDescToIdePlugins)
51+
import Ide.Plugin.Config (Config, formattingProvider)
52+
import Ide.PluginUtils (idePluginsToPluginDesc,
53+
pluginDescToIdePlugins)
5354
import Ide.Types
5455
import Language.LSP.Test
55-
import Language.LSP.Types hiding
56-
(SemanticTokenAbsolute (length, line),
57-
SemanticTokenRelative (length),
58-
SemanticTokensEdit (_start))
59-
import Language.LSP.Types.Capabilities (ClientCapabilities)
60-
import System.Directory (getCurrentDirectory,
61-
setCurrentDirectory)
56+
import Language.LSP.Types hiding
57+
(SemanticTokenAbsolute (length, line),
58+
SemanticTokenRelative (length),
59+
SemanticTokensEdit (_start))
60+
import Language.LSP.Types.Capabilities (ClientCapabilities)
61+
import System.Directory (canonicalizePath, copyFile,
62+
createDirectoryIfMissing,
63+
getCurrentDirectory,
64+
setCurrentDirectory)
6265
import System.FilePath
63-
import System.IO.Extra
64-
import System.IO.Unsafe (unsafePerformIO)
65-
import System.Process.Extra (createPipe)
66+
import System.IO.Extra (IOMode (ReadWriteMode),
67+
openFile, stderr,
68+
withTempFile)
69+
import System.IO.Unsafe (unsafePerformIO)
70+
import System.Process.Extra (createPipe)
6671
import System.Time.Extra
6772
import Test.Hls.Util
68-
import Test.Tasty hiding (Timeout)
73+
import Test.Tasty hiding (Timeout)
6974
import Test.Tasty.ExpectedFailure
7075
import Test.Tasty.Golden
7176
import Test.Tasty.HUnit
@@ -111,8 +116,9 @@ goldenWithHaskellDocFormatter
111116
-> (TextDocumentIdentifier -> Session ())
112117
-> TestTree
113118
goldenWithHaskellDocFormatter plugin formatter title testDataDir path desc ext act =
114-
goldenGitDiff title (testDataDir </> path <.> desc <.> ext)
115-
$ runSessionWithServerFormatter plugin formatter testDataDir
119+
goldenGitDiff title (testDataDir </> path <.> desc <.> ext) $
120+
runWithExtraFiles testDataDir $ \dir ->
121+
runSessionWithServerFormatter plugin formatter dir
116122
$ TL.encodeUtf8 . TL.fromStrict
117123
<$> do
118124
doc <- openDoc (path <.> ext) "haskell"
@@ -225,3 +231,24 @@ waitForBuildQueue = do
225231
ResponseMessage{_result=Right Null} -> return td
226232
-- assume a ghcide binary lacking the WaitForShakeQueue method
227233
_ -> return 0
234+
235+
runWithExtraFiles :: FilePath -> (FilePath -> IO a) -> IO a
236+
runWithExtraFiles testDataDir s = withTempDir $ \dir -> do
237+
copyTestDataFiles testDataDir dir
238+
s dir
239+
240+
-- | Version of 'System.IO.Extra.withTempDir' that canonicalizes the path
241+
-- Which we need to do on macOS since the $TMPDIR can be in @/private/var@ or
242+
-- @/var@
243+
withTempDir :: (FilePath -> IO a) -> IO a
244+
withTempDir f = withTempDir $ \dir -> do
245+
dir' <- canonicalizePath dir
246+
f dir'
247+
248+
copyTestDataFiles :: FilePath -> FilePath -> IO ()
249+
copyTestDataFiles testDataDir dir = do
250+
-- Copy all the test data files to the temporary workspace
251+
testDataFiles <- getDirectoryFilesIO testDataDir ["//*"]
252+
for_ testDataFiles $ \f -> do
253+
createDirectoryIfMissing True $ dir </> takeDirectory f
254+
copyFile (testDataDir </> f) (dir </> f)

0 commit comments

Comments
 (0)