Skip to content

Commit 70c56ea

Browse files
committed
Revert "always wait for restart"
This reverts commit 7bf6fde.
1 parent c778f9d commit 70c56ea

File tree

7 files changed

+37
-24
lines changed

7 files changed

+37
-24
lines changed

ghcide/session-loader/Development/IDE/Session.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -68,6 +68,7 @@ import Ide.Logger (Pretty (pretty),
6868
vcat, viaShow, (<+>))
6969
import Ide.Types (Config,
7070
SessionLoadingPreferenceConfig (..),
71+
ShouldWait (..),
7172
sessionLoading)
7273
import Language.LSP.Protocol.Message
7374
import Language.LSP.Server
@@ -625,7 +626,7 @@ loadSessionWithOptions recorder SessionLoadingOptions{..} rootDir que = do
625626
, ..
626627
}
627628
sessionShake = SessionShake
628-
{ restartSession = restartShakeSession extras
629+
{ restartSession = restartShakeSession extras ShouldWait
629630
, invalidateCache = invalidateShakeCache
630631
, enqueueActions = shakeEnqueue extras
631632
}

ghcide/src/Development/IDE/Core/FileStore.hs

Lines changed: 10 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -22,6 +22,7 @@ module Development.IDE.Core.FileStore(
2222
registerFileWatches,
2323
shareFilePath,
2424
Log(..),
25+
setSomethingModifiedWait,
2526
) where
2627

2728
import Control.Concurrent.STM.Stats (STM, atomically)
@@ -279,7 +280,7 @@ setFileModified recorder vfs state saved nfp actionBefore = do
279280
AlwaysCheck -> True
280281
CheckOnSave -> saved
281282
_ -> False
282-
restartShakeSession (shakeExtras state) vfs (fromNormalizedFilePath nfp ++ " (modified)") ([mkDelayedAction "ParentTC" L.Debug (typecheckParentsAction recorder nfp) | checkParents]) $ do
283+
restartShakeSession (shakeExtras state) ShouldNotWait vfs (fromNormalizedFilePath nfp ++ " (modified)") ([mkDelayedAction "ParentTC" L.Debug (typecheckParentsAction recorder nfp) | checkParents]) $ do
283284
keys<-actionBefore
284285
return (toKey GetModificationTime nfp:keys)
285286

@@ -299,11 +300,16 @@ typecheckParentsAction recorder nfp = do
299300
-- | Note that some keys have been modified and restart the session
300301
-- Only valid if the virtual file system was initialised by LSP, as that
301302
-- independently tracks which files are modified.
302-
setSomethingModified :: VFSModified -> IdeState -> String -> IO [Key] -> IO ()
303-
setSomethingModified vfs state reason actionBetweenSession = do
303+
setSomethingModified' :: ShouldWait -> VFSModified -> IdeState -> String -> IO [Key] -> IO ()
304+
setSomethingModified' shouldWait vfs state reason actionBetweenSession = do
304305
-- Update database to remove any files that might have been renamed/deleted
305306
atomically $ writeTaskQueue (indexQueue $ hiedbWriter $ shakeExtras state) (\withHieDb -> withHieDb deleteMissingRealFiles)
306-
void $ restartShakeSession (shakeExtras state) vfs reason [] actionBetweenSession
307+
void $ restartShakeSession (shakeExtras state) shouldWait vfs reason [] actionBetweenSession
308+
setSomethingModified :: VFSModified -> IdeState -> String -> IO [Key] -> IO ()
309+
setSomethingModified vfs state reason actionBetweenSession = setSomethingModified' ShouldNotWait vfs state reason actionBetweenSession
310+
311+
setSomethingModifiedWait :: VFSModified -> IdeState -> String -> IO [Key] -> IO ()
312+
setSomethingModifiedWait vfs state reason actionBetweenSession = setSomethingModified' ShouldWait vfs state reason actionBetweenSession
307313

308314
registerFileWatches :: [String] -> LSP.LspT Config IO Bool
309315
registerFileWatches globs = do

ghcide/src/Development/IDE/Core/Shake.hs

Lines changed: 14 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -345,7 +345,8 @@ data ShakeExtras = ShakeExtras
345345
,ideTesting :: IdeTesting
346346
-- ^ Whether to enable additional lsp messages used by the test suite for checking invariants
347347
,restartShakeSession
348-
:: VFSModified
348+
:: ShouldWait
349+
-> VFSModified
349350
-> String
350351
-> [DelayedAction ()]
351352
-> IO [Key]
@@ -888,16 +889,18 @@ instance Semigroup ShakeRestartArgs where
888889
-- | Restart the current 'ShakeSession' with the given system actions.
889890
-- Any actions running in the current session will be aborted,
890891
-- but actions added via 'shakeEnqueue' will be requeued.
891-
shakeRestart :: ShakeControlQueue -> VFSModified -> String -> [DelayedAction ()] -> IO [Key] -> IO ()
892-
shakeRestart rts vfs reason acts ioActionBetweenShakeSession = do
893-
waitMVar <- newEmptyMVar
894-
-- submit at the head of the queue,
895-
-- prefer restart request over any pending actions
896-
void $ submitWorkAtHead rts $ Left $
897-
toDyn $ ShakeRestartArgs vfs reason acts ioActionBetweenShakeSession 1 [waitMVar]
898-
-- Wait until the restart is done
899-
takeMVar waitMVar
900-
892+
shakeRestart :: ShakeControlQueue -> ShouldWait -> VFSModified -> String -> [DelayedAction ()] -> IO [Key] -> IO ()
893+
shakeRestart rts shouldWait vfs reason acts ioActionBetweenShakeSession = case shouldWait of
894+
ShouldWait -> do
895+
waitMVar <- newEmptyMVar
896+
-- submit at the head of the queue,
897+
-- prefer restart request over any pending actions
898+
void $ submitWorkAtHead rts $ Left $ toDyn $ ShakeRestartArgs vfs reason acts ioActionBetweenShakeSession 1 [waitMVar]
899+
-- Wait until the restart is done
900+
takeMVar waitMVar
901+
ShouldNotWait ->
902+
void $ submitWorkAtHead rts $ Left $
903+
toDyn $ ShakeRestartArgs vfs reason acts ioActionBetweenShakeSession 1 []
901904

902905
runRestartTaskDyn :: Recorder (WithPriority Log) -> MVar IdeState -> Dynamic -> IO ()
903906
runRestartTaskDyn recorder ideStateVar dy = runRestartTask recorder ideStateVar (dynShakeRestart dy)

hls-plugin-api/src/Ide/Types.hs

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -42,7 +42,7 @@ module Ide.Types
4242
, installSigUsr1Handler
4343
, lookupCommandProvider
4444
, ResolveFunction
45-
, mkResolveHandler
45+
, mkResolveHandler, ShouldWait(..)
4646
)
4747
where
4848

@@ -1302,3 +1302,6 @@ installSigUsr1Handler h = void $ installHandler sigUSR1 (Catch h) Nothing
13021302
resolve handlers for the same method, than our assumptions that we never have
13031303
two responses break, and behavior is undefined.
13041304
-}
1305+
1306+
data ShouldWait = ShouldWait | ShouldNotWait
1307+
deriving Eq

plugins/hls-cabal-plugin/src/Ide/Plugin/Cabal.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -179,7 +179,7 @@ Then we restart the shake session, so that changes to our virtual files are actu
179179
-}
180180
restartCabalShakeSession :: ShakeExtras -> VFS.VFS -> NormalizedFilePath -> String -> IO [Key] -> IO ()
181181
restartCabalShakeSession shakeExtras vfs file actionMsg actionBetweenSession = do
182-
restartShakeSession shakeExtras (VFSModified vfs) (fromNormalizedFilePath file ++ " " ++ actionMsg) [] $ do
182+
restartShakeSession shakeExtras ShouldNotWait (VFSModified vfs) (fromNormalizedFilePath file ++ " " ++ actionMsg) [] $ do
183183
keys <- actionBetweenSession
184184
return (toKey GetModificationTime file:keys)
185185

@@ -188,7 +188,7 @@ restartCabalShakeSession shakeExtras vfs file actionMsg actionBetweenSession = d
188188
-- rule to get re-run if the file changes on disk.
189189
restartCabalShakeSessionPhysical :: ShakeExtras -> VFS.VFS -> NormalizedFilePath -> String -> IO [Key] -> IO ()
190190
restartCabalShakeSessionPhysical shakeExtras vfs file actionMsg actionBetweenSession = do
191-
restartShakeSession shakeExtras (VFSModified vfs) (fromNormalizedFilePath file ++ " " ++ actionMsg) [] $ do
191+
restartShakeSession shakeExtras ShouldNotWait (VFSModified vfs) (fromNormalizedFilePath file ++ " " ++ actionMsg) [] $ do
192192
keys <- actionBetweenSession
193193
return (toKey GetModificationTime file:toKey GetPhysicalModificationTime file:keys)
194194

plugins/hls-eval-plugin/src/Ide/Plugin/Eval/Handlers.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -41,7 +41,7 @@ import Data.String (IsString)
4141
import Data.Text (Text)
4242
import qualified Data.Text as T
4343
import qualified Data.Text.Utf16.Rope.Mixed as Rope
44-
import Development.IDE.Core.FileStore (getUriContents, setSomethingModified)
44+
import Development.IDE.Core.FileStore (getUriContents, setSomethingModifiedWait)
4545
import Development.IDE.Core.Rules (IdeState,
4646
runAction)
4747
import Development.IDE.Core.Shake (use_, uses_, VFSModified (VFSUnmodified), useWithSeparateFingerprintRule_)
@@ -214,11 +214,11 @@ runEvalCmd recorder plId st mtoken EvalParams{..} =
214214

215215
-- enable codegen for the module which we need to evaluate.
216216
final_hscEnv <- liftIO $ bracket_
217-
(setSomethingModified VFSUnmodified st "Eval" $ do
217+
(setSomethingModifiedWait VFSUnmodified st "Eval" $ do
218218
queueForEvaluation st nfp
219219
return [toKey IsEvaluating nfp]
220220
)
221-
(setSomethingModified VFSUnmodified st "Eval" $ do
221+
(setSomethingModifiedWait VFSUnmodified st "Eval" $ do
222222
unqueueForEvaluation st nfp
223223
return [toKey IsEvaluating nfp]
224224
)

scripts/flaky-test-patterns.txt

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,7 @@
44
# open close
55
# non local variable
66
# Notification Handlers
7-
bidirectional module dependency with hs-boot
7+
# bidirectional module dependency with hs-boot
88

99
# InternalError over InvalidParams
1010
# ghcide restarts shake session on config changes:
@@ -19,7 +19,7 @@ bidirectional module dependency with hs-boot
1919
# hls-class-plugin-tests::Creates a placeholder for fmap
2020
# hls-rename-plugin-tests::Rename
2121
# th-linking-test-unboxed
22-
# update syntax error
22+
update syntax error
2323
# iface-error-test-1
2424

2525
# update syntax error

0 commit comments

Comments
 (0)