Skip to content

Commit 547dc32

Browse files
authored
Fix diagnostics update bug (haskell/ghcide#959)
* Preventively switch to uninterruptible mask in withMVar' withMVar' is used to update the shakeSession var and it's crucial that the third argument is not interrupted. 'mask' can still be interrupted for I/O actions and, while we were careful to ensure none was used, if it ever breaks it will lead to very hard to debug problems. * refactor: move to RuleTypes * Add a TestRequest to wait for arbitrary ide actions Closes haskell/ghcide#955 * expectCurrentDiagnostics * Add a test suite for cancellation * Introduce --test-no-kick to fix cancellation tests reliability * delete unsafeClearDiagnostics (unused) * GetModSummaryWithoutTimestamps - remove StringBuffer Since the contents of the buffer are not tracked by the fingerprint. * Fix diagnostics bug Given a FOI F with non null typechecking diagnostics D, imagine the following scenario: 1. An edit notification for F is received, creating a new version 2. GetModTime is executed, producing 0 diagnostics. 2.1 updateFileDiagnostics is called 2.2 setStageDiagnostics is called 2.3 LSP.updateDiagnostics is called with a new version, resetting all the diagnostics for F 2.4 newDiags=[] in updateFileDiagnostics, which is different from D (the last published diagnostics), which enqueues a new publishDiagnostics [] in the Debouncer 3. An edit notification for F is received before typechecking has a chance to run which undoes the previous edit 4. The debouncer publishes the empty set of diagnostics after waiting 0.1s 5. GetFileContents runs and since the contents of the file haven't changed since the last time it ran, early cutoff skips everything donwstream Since TypeCheck is skipped, the empty set of diagnostics stays published until another edit comes. The goal of this change is to prevent setStageDiagnostics from losing diagnostics from other stages. To achieve this, we recover the old diagnostics for all stages and merge them with the new stage. * Fix hlint * Use Map.insert for clarity * Fix redundant imports * Fix "code actions after edit" experiment"
1 parent a30e55f commit 547dc32

File tree

13 files changed

+309
-137
lines changed

13 files changed

+309
-137
lines changed

ghcide/bench/lib/Experiments.hs

Lines changed: 7 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -115,7 +115,13 @@ experiments =
115115
)
116116
( \p doc -> do
117117
changeDoc doc [hygienicEdit]
118-
whileM (null <$> waitForDiagnostics)
118+
waitForProgressDone
119+
-- NOTE ghcide used to clear and reinstall the diagnostics here
120+
-- new versions no longer do, but keep this logic around
121+
-- to benchmark old versions sucessfully
122+
diags <- getCurrentDiagnostics doc
123+
when (null diags) $
124+
whileM (null <$> waitForDiagnostics)
119125
not . null <$> getCodeActions doc (Range p p)
120126
)
121127
]

ghcide/exe/Arguments.hs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -14,6 +14,7 @@ data Arguments = Arguments
1414
,argsShakeProfiling :: Maybe FilePath
1515
,argsOTMemoryProfiling :: Bool
1616
,argsTesting :: Bool
17+
,argsDisableKick :: Bool
1718
,argsThreads :: Int
1819
,argsVerbose :: Bool
1920
}
@@ -35,5 +36,6 @@ arguments = Arguments
3536
<*> optional (strOption $ long "shake-profiling" <> metavar "DIR" <> help "Dump profiling reports to this directory")
3637
<*> switch (long "ot-memory-profiling" <> help "Record OpenTelemetry info to the eventlog. Needs the -l RTS flag to have an effect")
3738
<*> switch (long "test" <> help "Enable additional lsp messages used by the testsuite")
39+
<*> switch (long "test-no-kick" <> help "Disable kick. Useful for testing cancellation")
3840
<*> option auto (short 'j' <> help "Number of threads (0: automatic)" <> metavar "NUM" <> value 0 <> showDefault)
3941
<*> switch (long "verbose" <> help "Include internal events in logging output")

ghcide/exe/Main.hs

Lines changed: 9 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -118,7 +118,15 @@ main = do
118118
}
119119
logLevel = if argsVerbose then minBound else Info
120120
debouncer <- newAsyncDebouncer
121-
initialise caps (mainRule >> pluginRules plugins >> action kick)
121+
let rules = do
122+
-- install the main and ghcide-plugin rules
123+
mainRule
124+
pluginRules plugins
125+
-- install the kick action, which triggers a typecheck on every
126+
-- Shake database restart, i.e. on every user edit.
127+
unless argsDisableKick $
128+
action kick
129+
initialise caps rules
122130
getLspId event wProg wIndefProg (logger logLevel) debouncer options vfs
123131
else do
124132
-- GHC produces messages with UTF8 in them, so make sure the terminal doesn't error

ghcide/ghcide.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -41,6 +41,7 @@ library
4141
base == 4.*,
4242
binary,
4343
bytestring,
44+
case-insensitive,
4445
containers,
4546
data-default,
4647
deepseq,

ghcide/src/Development/IDE.hs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -28,7 +28,6 @@ import Development.IDE.Core.Shake as X
2828
ShakeExtras,
2929
IdeRule,
3030
define, defineEarlyCutoff,
31-
GetModificationTime(GetModificationTime),
3231
use, useNoFile, uses, useWithStale, useWithStaleFast, useWithStaleFast',
3332
FastResult(..),
3433
use_, useNoFile_, uses_, useWithStale_,

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

Lines changed: 0 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -28,7 +28,6 @@ import Control.Monad.Extra
2828
import Development.Shake
2929
import Development.Shake.Classes
3030
import Control.Exception
31-
import GHC.Generics
3231
import Data.Either.Extra
3332
import Data.Int (Int64)
3433
import Data.Time
@@ -100,15 +99,6 @@ isFileOfInterestRule = defineEarlyCutoff $ \IsFileOfInterest f -> do
10099
let res = maybe NotFOI IsFOI $ f `HM.lookup` filesOfInterest
101100
return (Just $ BS.pack $ show $ hash res, ([], Just res))
102101

103-
-- | Get the contents of a file, either dirty (if the buffer is modified) or Nothing to mean use from disk.
104-
type instance RuleResult GetFileContents = (FileVersion, Maybe T.Text)
105-
106-
data GetFileContents = GetFileContents
107-
deriving (Eq, Show, Generic)
108-
instance Hashable GetFileContents
109-
instance NFData GetFileContents
110-
instance Binary GetFileContents
111-
112102
getModificationTimeRule :: VFSHandle -> Rules ()
113103
getModificationTimeRule vfs =
114104
defineEarlyCutoff $ \(GetModificationTime_ missingFileDiags) file -> do

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

Lines changed: 52 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,7 @@
22
-- SPDX-License-Identifier: Apache-2.0
33

44
{-# LANGUAGE FlexibleInstances #-}
5+
{-# LANGUAGE PatternSynonyms #-}
56
{-# LANGUAGE TypeFamilies #-}
67
{-# LANGUAGE DerivingStrategies #-}
78

@@ -37,6 +38,8 @@ import Language.Haskell.LSP.Types (NormalizedFilePath)
3738
import TcRnMonad (TcGblEnv)
3839
import qualified Data.ByteString.Char8 as BS
3940
import Development.IDE.Types.Options (IdeGhcSession)
41+
import Data.Text (Text)
42+
import Data.Int (Int64)
4043

4144
data LinkableType = ObjectLinkable | BCOLinkable
4245
deriving (Eq,Ord,Show)
@@ -190,6 +193,55 @@ type instance RuleResult GetModIface = HiFileResult
190193
-- For better early cuttoff
191194
type instance RuleResult GetModIfaceWithoutLinkable = HiFileResult
192195

196+
-- | Get the contents of a file, either dirty (if the buffer is modified) or Nothing to mean use from disk.
197+
type instance RuleResult GetFileContents = (FileVersion, Maybe Text)
198+
199+
-- The Shake key type for getModificationTime queries
200+
data GetModificationTime = GetModificationTime_
201+
{ missingFileDiagnostics :: Bool
202+
-- ^ If false, missing file diagnostics are not reported
203+
}
204+
deriving (Show, Generic)
205+
206+
instance Eq GetModificationTime where
207+
-- Since the diagnostics are not part of the answer, the query identity is
208+
-- independent from the 'missingFileDiagnostics' field
209+
_ == _ = True
210+
211+
instance Hashable GetModificationTime where
212+
-- Since the diagnostics are not part of the answer, the query identity is
213+
-- independent from the 'missingFileDiagnostics' field
214+
hashWithSalt salt _ = salt
215+
216+
instance NFData GetModificationTime
217+
instance Binary GetModificationTime
218+
219+
pattern GetModificationTime :: GetModificationTime
220+
pattern GetModificationTime = GetModificationTime_ {missingFileDiagnostics=True}
221+
222+
-- | Get the modification time of a file.
223+
type instance RuleResult GetModificationTime = FileVersion
224+
225+
data FileVersion
226+
= VFSVersion !Int
227+
| ModificationTime
228+
!Int64 -- ^ Large unit (platform dependent, do not make assumptions)
229+
!Int64 -- ^ Small unit (platform dependent, do not make assumptions)
230+
deriving (Show, Generic)
231+
232+
instance NFData FileVersion
233+
234+
vfsVersion :: FileVersion -> Maybe Int
235+
vfsVersion (VFSVersion i) = Just i
236+
vfsVersion ModificationTime{} = Nothing
237+
238+
data GetFileContents = GetFileContents
239+
deriving (Eq, Show, Generic)
240+
instance Hashable GetFileContents
241+
instance NFData GetFileContents
242+
instance Binary GetFileContents
243+
244+
193245
data FileOfInterestStatus = OnDisk | Modified
194246
deriving (Eq, Show, Typeable, Generic)
195247
instance Hashable FileOfInterestStatus

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

Lines changed: 8 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -734,24 +734,26 @@ getModSummaryRule = do
734734
getModSummaryFromImports session fp modTime (textToStringBuffer <$> mFileContent)
735735
case modS of
736736
Right res@(ms,_) -> do
737-
let fingerPrint = hash (computeFingerprint f dflags ms, hashUTC modTime)
737+
let fingerPrint = hash (computeFingerprint f (fromJust $ ms_hspp_buf ms) dflags ms, hashUTC modTime)
738738
return ( Just (BS.pack $ show fingerPrint) , ([], Just res))
739739
Left diags -> return (Nothing, (diags, Nothing))
740740

741741
defineEarlyCutoff $ \GetModSummaryWithoutTimestamps f -> do
742742
ms <- use GetModSummary f
743743
case ms of
744744
Just res@(msWithTimestamps,_) -> do
745-
let ms = msWithTimestamps { ms_hs_date = error "use GetModSummary instead of GetModSummaryWithoutTimestamps" }
745+
let ms = msWithTimestamps {
746+
ms_hs_date = error "use GetModSummary instead of GetModSummaryWithoutTimestamps",
747+
ms_hspp_buf = error "use GetModSummary instead of GetModSummaryWithoutTimestamps"
748+
}
746749
dflags <- hsc_dflags . hscEnv <$> use_ GhcSession f
747-
-- include the mod time in the fingerprint
748-
let fp = BS.pack $ show $ hash (computeFingerprint f dflags ms)
750+
let fp = BS.pack $ show $ hash (computeFingerprint f (fromJust $ ms_hspp_buf msWithTimestamps) dflags ms)
749751
return (Just fp, ([], Just res))
750752
Nothing -> return (Nothing, ([], Nothing))
751753
where
752754
-- Compute a fingerprint from the contents of `ModSummary`,
753755
-- eliding the timestamps and other non relevant fields.
754-
computeFingerprint f dflags ModSummary{..} =
756+
computeFingerprint f sb dflags ModSummary{..} =
755757
let fingerPrint =
756758
( moduleNameString (moduleName ms_mod)
757759
, ms_hspp_file
@@ -761,7 +763,7 @@ getModSummaryRule = do
761763
, fingerPrintImports ms_textual_imps
762764
)
763765
fingerPrintImports = map (fmap uniq *** (moduleNameString . unLoc))
764-
opts = Hdr.getOptions dflags (fromJust ms_hspp_buf) (fromNormalizedFilePath f)
766+
opts = Hdr.getOptions dflags sb (fromNormalizedFilePath f)
765767
in fingerPrint
766768

767769
hashUTC UTCTime{..} = (fromEnum utctDay, fromEnum utctDayTime)

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

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -13,7 +13,7 @@ module Development.IDE.Core.Service(
1313
IdeState, initialise, shutdown,
1414
runAction,
1515
writeProfile,
16-
getDiagnostics, unsafeClearDiagnostics,
16+
getDiagnostics,
1717
ideLogger,
1818
updatePositionMapping,
1919
) where

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

Lines changed: 28 additions & 72 deletions
Original file line numberDiff line numberDiff line change
@@ -7,7 +7,6 @@
77
{-# LANGUAGE RecursiveDo #-}
88
{-# LANGUAGE TypeFamilies #-}
99
{-# LANGUAGE ConstraintKinds #-}
10-
{-# LANGUAGE PatternSynonyms #-}
1110

1211
-- | A Shake implementation of the compiler service.
1312
--
@@ -38,7 +37,7 @@ module Development.IDE.Core.Shake(
3837
useWithStale, usesWithStale,
3938
useWithStale_, usesWithStale_,
4039
define, defineEarlyCutoff, defineOnDisk, needOnDisk, needOnDisks,
41-
getDiagnostics, unsafeClearDiagnostics,
40+
getDiagnostics,
4241
getHiddenDiagnostics,
4342
IsIdeGlobal, addIdeGlobal, addIdeGlobalExtras, getIdeGlobalState, getIdeGlobalAction,
4443
getIdeGlobalExtras,
@@ -84,6 +83,7 @@ import Development.IDE.Core.Debouncer
8483
import Development.IDE.GHC.Compat (NameCacheUpdater(..), upNameCache )
8584
import Development.IDE.GHC.Orphans ()
8685
import Development.IDE.Core.PositionMapping
86+
import Development.IDE.Core.RuleTypes
8787
import Development.IDE.Types.Action
8888
import Development.IDE.Types.Logger hiding (Priority)
8989
import Development.IDE.Types.KnownTargets
@@ -124,7 +124,6 @@ import Data.IORef
124124
import NameCache
125125
import UniqSupply
126126
import PrelInfo
127-
import Data.Int (Int64)
128127
import Language.Haskell.LSP.Types.Capabilities
129128
import OpenTelemetry.Eventlog
130129

@@ -502,7 +501,7 @@ shakeShut IdeState{..} = withMVar shakeSession $ \runner -> do
502501
-- | This is a variant of withMVar where the first argument is run unmasked and if it throws
503502
-- an exception, the previous value is restored while the second argument is executed masked.
504503
withMVar' :: MVar a -> (a -> IO b) -> (b -> IO (a, c)) -> IO c
505-
withMVar' var unmasked masked = mask $ \restore -> do
504+
withMVar' var unmasked masked = uninterruptibleMask $ \restore -> do
506505
a <- takeMVar var
507506
b <- restore (unmasked a) `onException` putMVar var a
508507
(a', c) <- masked b
@@ -652,11 +651,6 @@ getHiddenDiagnostics IdeState{shakeExtras = ShakeExtras{hiddenDiagnostics}} = do
652651
val <- readVar hiddenDiagnostics
653652
return $ getAllDiagnostics val
654653

655-
-- | FIXME: This function is temporary! Only required because the files of interest doesn't work
656-
unsafeClearDiagnostics :: IdeState -> IO ()
657-
unsafeClearDiagnostics IdeState{shakeExtras = ShakeExtras{diagnostics}} =
658-
writeVar diagnostics mempty
659-
660654
-- | Clear the results for all files that do not match the given predicate.
661655
garbageCollect :: (NormalizedFilePath -> Bool) -> Action ()
662656
garbageCollect keep = do
@@ -998,25 +992,19 @@ updateFileDiagnostics :: MonadIO m
998992
updateFileDiagnostics fp k ShakeExtras{diagnostics, hiddenDiagnostics, publishedDiagnostics, state, debouncer, eventer} current = liftIO $ do
999993
modTime <- (currentValue =<<) <$> getValues state GetModificationTime fp
1000994
let (currentShown, currentHidden) = partition ((== ShowDiag) . fst) current
995+
uri = filePathToUri' fp
996+
ver = vfsVersion =<< modTime
997+
updateDiagnosticsWithForcing new store = do
998+
store' <- evaluate $ setStageDiagnostics uri ver (T.pack $ show k) new store
999+
new' <- evaluate $ getUriDiagnostics uri store'
1000+
return (store', new')
10011001
mask_ $ do
10021002
-- Mask async exceptions to ensure that updated diagnostics are always
10031003
-- published. Otherwise, we might never publish certain diagnostics if
10041004
-- an exception strikes between modifyVar but before
10051005
-- publishDiagnosticsNotification.
1006-
newDiags <- modifyVar diagnostics $ \old -> do
1007-
let newDiagsStore = setStageDiagnostics fp (vfsVersion =<< modTime)
1008-
(T.pack $ show k) (map snd currentShown) old
1009-
let newDiags = getFileDiagnostics fp newDiagsStore
1010-
_ <- evaluate newDiagsStore
1011-
_ <- evaluate newDiags
1012-
pure (newDiagsStore, newDiags)
1013-
modifyVar_ hiddenDiagnostics $ \old -> do
1014-
let newDiagsStore = setStageDiagnostics fp (vfsVersion =<< modTime)
1015-
(T.pack $ show k) (map snd currentHidden) old
1016-
let newDiags = getFileDiagnostics fp newDiagsStore
1017-
_ <- evaluate newDiagsStore
1018-
_ <- evaluate newDiags
1019-
return newDiagsStore
1006+
newDiags <- modifyVar diagnostics $ updateDiagnosticsWithForcing $ map snd currentShown
1007+
_ <- modifyVar hiddenDiagnostics $ updateDiagnosticsWithForcing $ map snd currentHidden
10201008
let uri = filePathToUri' fp
10211009
let delay = if null newDiags then 0.1 else 0
10221010
registerEvent debouncer delay uri $ do
@@ -1051,77 +1039,45 @@ actionLogger = do
10511039
return logger
10521040

10531041

1054-
-- The Shake key type for getModificationTime queries
1055-
data GetModificationTime = GetModificationTime_
1056-
{ missingFileDiagnostics :: Bool
1057-
-- ^ If false, missing file diagnostics are not reported
1058-
}
1059-
deriving (Show, Generic)
1060-
1061-
instance Eq GetModificationTime where
1062-
-- Since the diagnostics are not part of the answer, the query identity is
1063-
-- independent from the 'missingFileDiagnostics' field
1064-
_ == _ = True
1065-
1066-
instance Hashable GetModificationTime where
1067-
-- Since the diagnostics are not part of the answer, the query identity is
1068-
-- independent from the 'missingFileDiagnostics' field
1069-
hashWithSalt salt _ = salt
1070-
1071-
instance NFData GetModificationTime
1072-
instance Binary GetModificationTime
1073-
1074-
pattern GetModificationTime :: GetModificationTime
1075-
pattern GetModificationTime = GetModificationTime_ {missingFileDiagnostics=True}
1076-
1077-
-- | Get the modification time of a file.
1078-
type instance RuleResult GetModificationTime = FileVersion
1079-
1080-
data FileVersion
1081-
= VFSVersion !Int
1082-
| ModificationTime
1083-
!Int64 -- ^ Large unit (platform dependent, do not make assumptions)
1084-
!Int64 -- ^ Small unit (platform dependent, do not make assumptions)
1085-
deriving (Show, Generic)
1086-
1087-
instance NFData FileVersion
1088-
1089-
vfsVersion :: FileVersion -> Maybe Int
1090-
vfsVersion (VFSVersion i) = Just i
1091-
vfsVersion ModificationTime{} = Nothing
1092-
10931042
getDiagnosticsFromStore :: StoreItem -> [Diagnostic]
10941043
getDiagnosticsFromStore (StoreItem _ diags) = concatMap SL.fromSortedList $ Map.elems diags
10951044

10961045

10971046
-- | Sets the diagnostics for a file and compilation step
10981047
-- if you want to clear the diagnostics call this with an empty list
10991048
setStageDiagnostics
1100-
:: NormalizedFilePath
1049+
:: NormalizedUri
11011050
-> TextDocumentVersion -- ^ the time that the file these diagnostics originate from was last edited
11021051
-> T.Text
11031052
-> [LSP.Diagnostic]
11041053
-> DiagnosticStore
11051054
-> DiagnosticStore
1106-
setStageDiagnostics fp timeM stage diags ds =
1107-
updateDiagnostics ds uri timeM diagsBySource
1108-
where
1109-
diagsBySource = Map.singleton (Just stage) (SL.toSortedList diags)
1110-
uri = filePathToUri' fp
1055+
setStageDiagnostics uri ver stage diags ds = newDiagsStore where
1056+
-- When 'ver' is a new version, updateDiagnostics throws away diagnostics from all stages
1057+
-- This interacts bady with early cutoff, so we make sure to preserve diagnostics
1058+
-- from other stages when calling updateDiagnostics
1059+
-- But this means that updateDiagnostics cannot be called concurrently
1060+
-- for different stages anymore
1061+
updatedDiags = Map.insert (Just stage) (SL.toSortedList diags) oldDiags
1062+
oldDiags = case HMap.lookup uri ds of
1063+
Just (StoreItem _ byStage) -> byStage
1064+
_ -> Map.empty
1065+
newDiagsStore = updateDiagnostics ds uri ver updatedDiags
1066+
11111067

11121068
getAllDiagnostics ::
11131069
DiagnosticStore ->
11141070
[FileDiagnostic]
11151071
getAllDiagnostics =
11161072
concatMap (\(k,v) -> map (fromUri k,ShowDiag,) $ getDiagnosticsFromStore v) . HMap.toList
11171073

1118-
getFileDiagnostics ::
1119-
NormalizedFilePath ->
1074+
getUriDiagnostics ::
1075+
NormalizedUri ->
11201076
DiagnosticStore ->
11211077
[LSP.Diagnostic]
1122-
getFileDiagnostics fp ds =
1078+
getUriDiagnostics uri ds =
11231079
maybe [] getDiagnosticsFromStore $
1124-
HMap.lookup (filePathToUri' fp) ds
1080+
HMap.lookup uri ds
11251081

11261082
filterDiagnostics ::
11271083
(NormalizedFilePath -> Bool) ->

0 commit comments

Comments
 (0)