Skip to content

Commit e52cffe

Browse files
authored
Make iface-error-test-1 less flaky (#2882)
* remove duplicate log message * Fix expectNoMoreDiagnostics * redundant import * dead code * unnecessary do section * redundant log message * waitForProgressDone to improve consistency * redundant import
1 parent 65fbc5e commit e52cffe

File tree

6 files changed

+12
-39
lines changed

6 files changed

+12
-39
lines changed

Diff for: ghcide/src/Development/IDE/Core/Debouncer.hs

+2-3
Original file line numberDiff line numberDiff line change
@@ -50,9 +50,8 @@ asyncRegisterEvent d delay k fire = mask_ $ do
5050
sleep delay
5151
fire
5252
atomically $ STM.delete k d
53-
do
54-
prev <- atomicallyNamed "debouncer" $ STM.focus (Focus.lookup <* Focus.insert a) k d
55-
traverse_ cancel prev
53+
prev <- atomicallyNamed "debouncer" $ STM.focus (Focus.lookup <* Focus.insert a) k d
54+
traverse_ cancel prev
5655

5756
-- | Debouncer used in the DAML CLI compiler that emits events immediately.
5857
noopDebouncer :: Debouncer k

Diff for: ghcide/src/Development/IDE/Core/FileStore.hs

-7
Original file line numberDiff line numberDiff line change
@@ -28,7 +28,6 @@ import Control.Exception
2828
import Control.Monad.Extra
2929
import Control.Monad.IO.Class
3030
import qualified Data.ByteString as BS
31-
import Data.Either.Extra
3231
import qualified Data.Rope.UTF16 as Rope
3332
import qualified Data.Text as T
3433
import Data.Time
@@ -192,12 +191,6 @@ getFileContentsImpl file = do
192191
pure $ Rope.toText . _text <$> mbVirtual
193192
pure ([], Just (time, res))
194193

195-
ideTryIOException :: NormalizedFilePath -> IO a -> IO (Either FileDiagnostic a)
196-
ideTryIOException fp act =
197-
mapLeft
198-
(\(e :: IOException) -> ideErrorText fp $ T.pack $ show e)
199-
<$> try act
200-
201194
-- | Returns the modification time and the contents.
202195
-- For VFS paths, the modification time is the current time.
203196
getFileContents :: NormalizedFilePath -> Action (UTCTime, Maybe T.Text)

Diff for: ghcide/src/Development/IDE/Core/OfInterest.hs

+3-3
Original file line numberDiff line numberDiff line change
@@ -107,10 +107,10 @@ addFileOfInterest state f v = do
107107
(prev, files) <- modifyVar var $ \dict -> do
108108
let (prev, new) = HashMap.alterF (, Just v) f dict
109109
pure (new, (prev, new))
110-
when (prev /= Just v) $
110+
when (prev /= Just v) $ do
111111
join $ atomically $ recordDirtyKeys (shakeExtras state) IsFileOfInterest [f]
112-
logDebug (ideLogger state) $
113-
"Set files of interest to: " <> T.pack (show files)
112+
logDebug (ideLogger state) $
113+
"Set files of interest to: " <> T.pack (show files)
114114

115115
deleteFileOfInterest :: IdeState -> NormalizedFilePath -> IO ()
116116
deleteFileOfInterest state f = do

Diff for: ghcide/src/Development/IDE/Core/Shake.hs

-23
Original file line numberDiff line numberDiff line change
@@ -696,17 +696,6 @@ shakeRestart recorder IdeState{..} vfs reason acts =
696696
queue <- atomicallyNamed "actionQueue - peek" $ peekInProgress $ actionQueue shakeExtras
697697

698698
log Debug $ LogBuildSessionRestart reason queue backlog stopTime res
699-
700-
let profile = case res of
701-
Just fp -> ", profile saved at " <> fp
702-
_ -> ""
703-
-- TODO: should replace with logging using a logger that sends lsp message
704-
let msg = T.pack $ "Restarting build session " ++ reason' ++ queueMsg ++ keysMsg ++ abortMsg
705-
reason' = "due to " ++ reason
706-
queueMsg = " with queue " ++ show (map actionName queue)
707-
keysMsg = " for keys " ++ show (HSet.toList backlog) ++ " "
708-
abortMsg = "(aborting the previous one took " ++ showDuration stopTime ++ profile ++ ")"
709-
notifyTestingLogMessage shakeExtras msg
710699
)
711700
-- It is crucial to be masked here, otherwise we can get killed
712701
-- between spawning the new thread and updating shakeSession.
@@ -719,13 +708,6 @@ shakeRestart recorder IdeState{..} vfs reason acts =
719708
sleep seconds
720709
logWith recorder Error (LogBuildSessionRestartTakingTooLong seconds)
721710

722-
notifyTestingLogMessage :: ShakeExtras -> T.Text -> IO ()
723-
notifyTestingLogMessage extras msg = do
724-
(IdeTesting isTestMode) <- optTesting <$> getIdeOptionsIO extras
725-
let notif = LSP.LogMessageParams LSP.MtLog msg
726-
when isTestMode $ mRunLspT (lspEnv extras) $ LSP.sendNotification LSP.SWindowLogMessage notif
727-
728-
729711
-- | Enqueue an action in the existing 'ShakeSession'.
730712
-- Returns a computation to block until the action is run, propagating exceptions.
731713
-- Assumes a 'ShakeSession' is available.
@@ -797,17 +779,12 @@ newSession recorder extras@ShakeExtras{..} vfsMod shakeDb acts reason = do
797779
let keysActs = pumpActionThread otSpan : map (run otSpan) (reenqueued ++ acts)
798780
res <- try @SomeException $
799781
restore $ shakeRunDatabaseForKeys (HSet.toList <$> allPendingKeys) shakeDb keysActs
800-
let res' = case res of
801-
Left e -> "exception: " <> displayException e
802-
Right _ -> "completed"
803-
let msg = T.pack $ "Finishing build session(" ++ res' ++ ")"
804782
return $ do
805783
let exception =
806784
case res of
807785
Left e -> Just e
808786
_ -> Nothing
809787
logWith recorder Debug $ LogBuildSessionFinish exception
810-
notifyTestingLogMessage extras msg
811788

812789
-- Do the work in a background thread
813790
workThread <- asyncWithUnmask workRun

Diff for: ghcide/test/exe/Main.hs

+6-2
Original file line numberDiff line numberDiff line change
@@ -22,7 +22,7 @@ import Control.Exception (bracket_, catch,
2222
import qualified Control.Lens as Lens
2323
import Control.Monad
2424
import Control.Monad.IO.Class (MonadIO, liftIO)
25-
import Data.Aeson (fromJSON, toJSON)
25+
import Data.Aeson (toJSON)
2626
import qualified Data.Aeson as A
2727
import Data.Default
2828
import Data.Foldable
@@ -6075,11 +6075,14 @@ ifaceErrorTest = testCase "iface-error-test-1" $ runWithExtraFiles "recomp" $ \d
60756075
expectDiagnostics
60766076
[("P.hs", [(DsWarning,(4,0), "Top-level binding")])] -- So what we know P has been loaded
60776077

6078+
waitForProgressDone
6079+
60786080
-- Change y from Int to B
60796081
changeDoc bdoc [TextDocumentContentChangeEvent Nothing Nothing $ T.unlines ["module B where", "y :: Bool", "y = undefined"]]
60806082
-- save so that we can that the error propogates to A
60816083
sendNotification STextDocumentDidSave (DidSaveTextDocumentParams bdoc Nothing)
60826084

6085+
60836086
-- Check that the error propogates to A
60846087
expectDiagnostics
60856088
[("A.hs", [(DsError, (5, 4), "Couldn't match expected type 'Int' with actual type 'Bool'")])]
@@ -6090,7 +6093,8 @@ ifaceErrorTest = testCase "iface-error-test-1" $ runWithExtraFiles "recomp" $ \d
60906093
hi_exists <- liftIO $ doesFileExist $ hidir </> "B.hi"
60916094
liftIO $ assertBool ("Couldn't find B.hi in " ++ hidir) hi_exists
60926095

6093-
pdoc <- createDoc pPath "haskell" pSource
6096+
pdoc <- openDoc pPath "haskell"
6097+
waitForProgressDone
60946098
changeDoc pdoc [TextDocumentContentChangeEvent Nothing Nothing $ pSource <> "\nfoo = y :: Bool" ]
60956099
-- Now in P we have
60966100
-- bar = x :: Int

Diff for: ghcide/test/src/Development/IDE/Test.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -83,7 +83,7 @@ expectNoMoreDiagnostics timeout =
8383
expectMessages STextDocumentPublishDiagnostics timeout $ \diagsNot -> do
8484
let fileUri = diagsNot ^. params . uri
8585
actual = diagsNot ^. params . diagnostics
86-
liftIO $
86+
unless (actual == List []) $ liftIO $
8787
assertFailure $
8888
"Got unexpected diagnostics for " <> show fileUri
8989
<> " got "

0 commit comments

Comments
 (0)