@@ -12,13 +12,14 @@ import Data.Aeson (fromJSON)
1212import Data.Aeson.Types (Result (Success ))
1313import Data.List (isInfixOf )
1414import Data.List.Extra (nubOrdOn )
15+ import qualified Data.Text as T
16+ import Ide.Plugin.Config (checkProject )
1517import qualified Ide.Plugin.Eval as Eval
1618import Ide.Plugin.Eval.Types (EvalParams (.. ), Section (.. ),
1719 testOutput )
1820import Language.LSP.Types.Lens (arguments , command , range , title )
1921import System.FilePath ((</>) )
2022import Test.Hls
21- import qualified Data.Text as T
2223
2324main :: IO ()
2425main = defaultTestRunner tests
@@ -30,27 +31,27 @@ tests :: TestTree
3031tests =
3132 testGroup " eval"
3233 [ testCase " Produces Evaluate code lenses" $
33- runSessionWithServer evalPlugin testDataDir $ do
34+ runS evalPlugin testDataDir $ do
3435 doc <- openDoc " T1.hs" " haskell"
3536 lenses <- getCodeLenses doc
3637 liftIO $ map (preview $ command . _Just . title) lenses @?= [Just " Evaluate..." ]
3738 , testCase " Produces Refresh code lenses" $
38- runSessionWithServer evalPlugin testDataDir $ do
39+ runS evalPlugin testDataDir $ do
3940 doc <- openDoc " T2.hs" " haskell"
4041 lenses <- getCodeLenses doc
4142 liftIO $ map (preview $ command . _Just . title) lenses @?= [Just " Refresh..." ]
4243 , testCase " Code lenses have ranges" $
43- runSessionWithServer evalPlugin testDataDir $ do
44+ runS evalPlugin testDataDir $ do
4445 doc <- openDoc " T1.hs" " haskell"
4546 lenses <- getCodeLenses doc
4647 liftIO $ map (view range) lenses @?= [Range (Position 4 0 ) (Position 5 0 )]
4748 , testCase " Multi-line expressions have a multi-line range" $ do
48- runSessionWithServer evalPlugin testDataDir $ do
49+ runS evalPlugin testDataDir $ do
4950 doc <- openDoc " T3.hs" " haskell"
5051 lenses <- getCodeLenses doc
5152 liftIO $ map (view range) lenses @?= [Range (Position 3 0 ) (Position 5 0 )]
5253 , testCase " Executed expressions range covers only the expression" $ do
53- runSessionWithServer evalPlugin testDataDir $ do
54+ runS evalPlugin testDataDir $ do
5455 doc <- openDoc " T2.hs" " haskell"
5556 lenses <- getCodeLenses doc
5657 liftIO $ map (view range) lenses @?= [Range (Position 4 0 ) (Position 5 0 )]
@@ -181,7 +182,7 @@ tests =
181182
182183goldenWithEval :: TestName -> FilePath -> FilePath -> TestTree
183184goldenWithEval title path ext =
184- goldenWithHaskellDoc evalPlugin title testDataDir path " expected" ext executeLensesBackwards
185+ goldenWithHaskellDoc (runS evalPlugin testDataDir) title testDataDir path " expected" ext executeLensesBackwards
185186
186187-- | Execute lenses backwards, to avoid affecting their position in the source file
187188executeLensesBackwards :: TextDocumentIdentifier -> Session ()
@@ -208,7 +209,7 @@ executeCmd cmd = do
208209 pure ()
209210
210211evalLenses :: FilePath -> IO [CodeLens ]
211- evalLenses path = runSessionWithServer evalPlugin testDataDir $ do
212+ evalLenses path = runS evalPlugin testDataDir $ do
212213 doc <- openDoc path " haskell"
213214 executeLensesBackwards doc
214215 getCodeLenses doc
@@ -225,11 +226,17 @@ testDataDir :: FilePath
225226testDataDir = " test" </> " testdata"
226227
227228evalInFile :: FilePath -> T. Text -> T. Text -> IO ()
228- evalInFile fp e expected = runSessionWithServer evalPlugin testDataDir $ do
229+ evalInFile fp e expected = runS evalPlugin testDataDir $ do
229230 doc <- openDoc fp " haskell"
230231 origin <- documentContents doc
231232 let withEval = origin <> e
232233 changeDoc doc [TextDocumentContentChangeEvent Nothing Nothing withEval]
233234 executeLensesBackwards doc
234235 result <- fmap T. strip . T. stripPrefix withEval <$> documentContents doc
235236 liftIO $ result @?= Just (T. strip expected)
237+
238+ -- Run with checkProject false to avoid loading all the test data modules,
239+ -- which leads to flaky test failures due to how the Eval plugin mutates
240+ -- the shared GHC session (this is because of how the InteractiveContext works)
241+ runS :: PluginDescriptor IdeState -> FilePath -> Session a -> IO a
242+ runS plugin = runSessionWithServer' [plugin] def{checkProject = False } def fullCaps
0 commit comments