@@ -27,8 +27,9 @@ import Ide.Types (IdePlugins (IdePlugins))
2727import Language.LSP.Protocol.Lens (arguments , command , range ,
2828 title )
2929import Language.LSP.Protocol.Message hiding (error )
30- import System.FilePath ((</>) )
30+ import System.FilePath ((<.>) , (< />) )
3131import Test.Hls
32+ import qualified Test.Hls.FileSystem as FS
3233
3334main :: IO ()
3435main = defaultTestRunner tests
@@ -40,27 +41,27 @@ tests :: TestTree
4041tests =
4142 testGroup " eval"
4243 [ testCase " Produces Evaluate code lenses" $
43- runSessionWithServer evalPlugin testDataDir $ do
44+ runSessionWithServerInTmpDir evalPlugin (mkFs $ FS. directProject " T1.hs " ) $ do
4445 doc <- openDoc " T1.hs" " haskell"
4546 lenses <- getCodeLenses doc
4647 liftIO $ map (preview $ command . _Just . title) lenses @?= [Just " Evaluate..." ]
4748 , testCase " Produces Refresh code lenses" $
48- runSessionWithServer evalPlugin testDataDir $ do
49+ runSessionWithServerInTmpDir evalPlugin (mkFs $ FS. directProject " T2.hs " ) $ do
4950 doc <- openDoc " T2.hs" " haskell"
5051 lenses <- getCodeLenses doc
5152 liftIO $ map (preview $ command . _Just . title) lenses @?= [Just " Refresh..." ]
5253 , testCase " Code lenses have ranges" $
53- runSessionWithServer evalPlugin testDataDir $ do
54+ runSessionWithServerInTmpDir evalPlugin (mkFs $ FS. directProject " T1.hs " ) $ do
5455 doc <- openDoc " T1.hs" " haskell"
5556 lenses <- getCodeLenses doc
5657 liftIO $ map (view range) lenses @?= [Range (Position 4 0 ) (Position 5 0 )]
5758 , testCase " Multi-line expressions have a multi-line range" $ do
58- runSessionWithServer evalPlugin testDataDir $ do
59+ runSessionWithServerInTmpDir evalPlugin (mkFs $ FS. directProject " T3.hs " ) $ do
5960 doc <- openDoc " T3.hs" " haskell"
6061 lenses <- getCodeLenses doc
6162 liftIO $ map (view range) lenses @?= [Range (Position 3 0 ) (Position 5 0 )]
6263 , testCase " Executed expressions range covers only the expression" $ do
63- runSessionWithServer evalPlugin testDataDir $ do
64+ runSessionWithServerInTmpDir evalPlugin (mkFs $ FS. directProject " T2.hs " ) $ do
6465 doc <- openDoc " T2.hs" " haskell"
6566 lenses <- getCodeLenses doc
6667 liftIO $ map (view range) lenses @?= [Range (Position 4 0 ) (Position 5 0 )]
@@ -122,15 +123,15 @@ tests =
122123 ]
123124 , goldenWithEval " :kind! treats a multilined result properly" " T24" " hs"
124125 , goldenWithEval " :kind treats a multilined result properly" " T25" " hs"
125- , goldenWithEval " local imports" " T26" " hs"
126+ , goldenWithEvalAndFs " local imports" ( FS. directProjectMulti [ " T26.hs " , " Util.hs " ]) " T26" " hs"
126127 , goldenWithEval " Preserves one empty comment line after prompt" " T27" " hs"
127128 , goldenWithEval " Multi line comments" " TMulti" " hs"
128129 , goldenWithEval " Multi line comments, with the last test line ends without newline" " TEndingMulti" " hs"
129130 , goldenWithEval " Evaluate expressions in Plain comments in both single line and multi line format" " TPlainComment" " hs"
130131 , goldenWithEval " Evaluate expressions in Haddock comments in both single line and multi line format" " THaddock" " hs"
131132 , goldenWithEval " Compare results (for Haddock tests only)" " TCompare" " hs"
132- , goldenWithEval " Local Modules imports are accessible in a test" " TLocalImport" " hs"
133- , goldenWithEval " Transitive local dependency" " TTransitive" " hs"
133+ , goldenWithEvalAndFs " Local Modules imports are accessible in a test" ( FS. directProjectMulti [ " TLocalImport.hs " , " Util.hs " ]) " TLocalImport" " hs"
134+ , goldenWithEvalAndFs " Transitive local dependency" ( FS. directProjectMulti [ " TTransitive.hs " , " TLocalImport.hs " , " Util.hs " ]) " TTransitive" " hs"
134135 -- , goldenWithEval "Local Modules can be imported in a test" "TLocalImportInTest" "hs"
135136 , goldenWithEval " Setting language option TupleSections" " TLanguageOptionsTupleSections" " hs"
136137 , goldenWithEval' " :set accepts ghci flags" " TFlags" " hs" (if ghcVersion >= GHC92 then " ghc92.expected" else " expected" )
@@ -142,8 +143,8 @@ tests =
142143 else " -- id :: forall {a}. a -> a" )
143144 , goldenWithEval " The default language extensions for the eval plugin are the same as those for ghci" " TSameDefaultLanguageExtensionsAsGhci" " hs"
144145 , goldenWithEval " IO expressions are supported, stdout/stderr output is ignored" " TIO" " hs"
145- , goldenWithEval " Property checking" " TProperty" " hs"
146- , goldenWithEval ' " Property checking with exception" " TPropertyError" " hs" (
146+ , goldenWithEvalAndFs " Property checking" cabalProjectFS " TProperty" " hs"
147+ , goldenWithEvalAndFs ' " Property checking with exception" cabalProjectFS " TPropertyError" " hs" (
147148 if ghcVersion >= GHC96 then
148149 " ghc96.expected"
149150 else if ghcVersion >= GHC94 && hostOS == Windows then
@@ -212,7 +213,7 @@ tests =
212213 not (" Baz Foo" `isInfixOf` output) @? " Output includes instance Baz Foo"
213214 ]
214215 , testCase " Interfaces are reused after Eval" $ do
215- runSessionWithServer evalPlugin testDataDir $ do
216+ runSessionWithServerInTmpDir evalPlugin (mkFs $ FS. directProjectMulti [ " TLocalImport.hs " , " Util.hs " ]) $ do
216217 doc <- openDoc " TLocalImport.hs" " haskell"
217218 waitForTypecheck doc
218219 lenses <- getCodeLenses doc
@@ -231,13 +232,22 @@ tests =
231232
232233goldenWithEval :: TestName -> FilePath -> FilePath -> TestTree
233234goldenWithEval title path ext =
234- goldenWithHaskellDoc evalPlugin title testDataDir path " expected" ext executeLensesBackwards
235+ goldenWithHaskellDocInTmpDir evalPlugin title (mkFs $ FS. directProject (path <.> ext)) path " expected" ext executeLensesBackwards
236+
237+ goldenWithEvalAndFs :: TestName -> [FS. FileTree ] -> FilePath -> FilePath -> TestTree
238+ goldenWithEvalAndFs title tree path ext =
239+ goldenWithHaskellDocInTmpDir evalPlugin title (mkFs tree) path " expected" ext executeLensesBackwards
235240
236241-- | Similar function as 'goldenWithEval' with an alternate reference file
237242-- naming. Useful when reference file may change because of GHC version.
238243goldenWithEval' :: TestName -> FilePath -> FilePath -> FilePath -> TestTree
239244goldenWithEval' title path ext expected =
240- goldenWithHaskellDoc evalPlugin title testDataDir path expected ext executeLensesBackwards
245+ goldenWithHaskellDocInTmpDir evalPlugin title (mkFs $ FS. directProject (path <.> ext)) path expected ext executeLensesBackwards
246+
247+ goldenWithEvalAndFs' :: TestName -> [FS. FileTree ] -> FilePath -> FilePath -> FilePath -> TestTree
248+ goldenWithEvalAndFs' title tree path ext expected =
249+ goldenWithHaskellDocInTmpDir evalPlugin title (mkFs tree) path expected ext executeLensesBackwards
250+
241251
242252-- | Execute lenses backwards, to avoid affecting their position in the source file
243253executeLensesBackwards :: TextDocumentIdentifier -> Session ()
@@ -264,7 +274,7 @@ executeCmd cmd = do
264274 pure ()
265275
266276evalLenses :: FilePath -> IO [CodeLens ]
267- evalLenses path = runSessionWithServer evalPlugin testDataDir $ do
277+ evalLenses path = runSessionWithServerInTmpDir evalPlugin (mkFs cabalProjectFS) $ do
268278 doc <- openDoc path " haskell"
269279 executeLensesBackwards doc
270280 getCodeLenses doc
@@ -298,16 +308,43 @@ exceptionConfig exCfg = changeConfig ["exception" .= exCfg]
298308
299309goldenWithEvalConfig' :: TestName -> FilePath -> FilePath -> FilePath -> Config -> TestTree
300310goldenWithEvalConfig' title path ext expected cfg =
301- goldenWithHaskellDoc evalPlugin title testDataDir path expected ext $ \ doc -> do
311+ goldenWithHaskellDocInTmpDir evalPlugin title (mkFs $ FS. directProject $ path <.> ext) path expected ext $ \ doc -> do
302312 sendConfigurationChanged (toJSON cfg)
303313 executeLensesBackwards doc
304314
305315evalInFile :: HasCallStack => FilePath -> T. Text -> T. Text -> IO ()
306- evalInFile fp e expected = runSessionWithServer evalPlugin testDataDir $ do
316+ evalInFile fp e expected = runSessionWithServerInTmpDir evalPlugin (mkFs $ FS. directProject fp) $ do
307317 doc <- openDoc fp " haskell"
308318 origin <- documentContents doc
309319 let withEval = origin <> e
310320 changeDoc doc [TextDocumentContentChangeEvent . InR . (.==) # text $ withEval]
311321 executeLensesBackwards doc
312322 result <- fmap T. strip . T. stripPrefix withEval <$> documentContents doc
313323 liftIO $ result @?= Just (T. strip expected)
324+
325+ -- ----------------------------------------------------------------------------
326+ -- File system definitions
327+ -- Used for declaring a test file tree
328+ -- ----------------------------------------------------------------------------
329+
330+ mkFs :: [FS. FileTree ] -> FS. VirtualFileTree
331+ mkFs = FS. mkVirtualFileTree testDataDir
332+
333+ cabalProjectFS :: [FS. FileTree ]
334+ cabalProjectFS = FS. simpleCabalProject'
335+ [ FS. copy " test.cabal"
336+ , FS. file " cabal.project"
337+ (FS. text " packages: ./info-util .\n "
338+ )
339+ , FS. copy " TProperty.hs"
340+ , FS. copy " TPropertyError.hs"
341+ , FS. copy " TI_Info.hs"
342+ , FS. copy " TInfo.hs"
343+ , FS. copy " TInfoBang.hs"
344+ , FS. copy " TInfoBangMany.hs"
345+ , FS. copy " TInfoMany.hs"
346+ , FS. directory " info-util"
347+ [ FS. copy " info-util/info-util.cabal"
348+ , FS. copy " info-util/InfoUtil.hs"
349+ ]
350+ ]
0 commit comments