|
7 | 7 | {-# LANGUAGE RecursiveDo #-}
|
8 | 8 | {-# LANGUAGE TypeFamilies #-}
|
9 | 9 | {-# LANGUAGE ConstraintKinds #-}
|
10 |
| -{-# LANGUAGE PatternSynonyms #-} |
11 | 10 |
|
12 | 11 | -- | A Shake implementation of the compiler service.
|
13 | 12 | --
|
@@ -38,7 +37,7 @@ module Development.IDE.Core.Shake(
|
38 | 37 | useWithStale, usesWithStale,
|
39 | 38 | useWithStale_, usesWithStale_,
|
40 | 39 | define, defineEarlyCutoff, defineOnDisk, needOnDisk, needOnDisks,
|
41 |
| - getDiagnostics, unsafeClearDiagnostics, |
| 40 | + getDiagnostics, |
42 | 41 | getHiddenDiagnostics,
|
43 | 42 | IsIdeGlobal, addIdeGlobal, addIdeGlobalExtras, getIdeGlobalState, getIdeGlobalAction,
|
44 | 43 | getIdeGlobalExtras,
|
@@ -84,6 +83,7 @@ import Development.IDE.Core.Debouncer
|
84 | 83 | import Development.IDE.GHC.Compat (NameCacheUpdater(..), upNameCache )
|
85 | 84 | import Development.IDE.GHC.Orphans ()
|
86 | 85 | import Development.IDE.Core.PositionMapping
|
| 86 | +import Development.IDE.Core.RuleTypes |
87 | 87 | import Development.IDE.Types.Action
|
88 | 88 | import Development.IDE.Types.Logger hiding (Priority)
|
89 | 89 | import Development.IDE.Types.KnownTargets
|
@@ -124,7 +124,6 @@ import Data.IORef
|
124 | 124 | import NameCache
|
125 | 125 | import UniqSupply
|
126 | 126 | import PrelInfo
|
127 |
| -import Data.Int (Int64) |
128 | 127 | import Language.Haskell.LSP.Types.Capabilities
|
129 | 128 | import OpenTelemetry.Eventlog
|
130 | 129 |
|
@@ -502,7 +501,7 @@ shakeShut IdeState{..} = withMVar shakeSession $ \runner -> do
|
502 | 501 | -- | This is a variant of withMVar where the first argument is run unmasked and if it throws
|
503 | 502 | -- an exception, the previous value is restored while the second argument is executed masked.
|
504 | 503 | 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 |
506 | 505 | a <- takeMVar var
|
507 | 506 | b <- restore (unmasked a) `onException` putMVar var a
|
508 | 507 | (a', c) <- masked b
|
@@ -652,11 +651,6 @@ getHiddenDiagnostics IdeState{shakeExtras = ShakeExtras{hiddenDiagnostics}} = do
|
652 | 651 | val <- readVar hiddenDiagnostics
|
653 | 652 | return $ getAllDiagnostics val
|
654 | 653 |
|
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 |
| - |
660 | 654 | -- | Clear the results for all files that do not match the given predicate.
|
661 | 655 | garbageCollect :: (NormalizedFilePath -> Bool) -> Action ()
|
662 | 656 | garbageCollect keep = do
|
@@ -998,25 +992,19 @@ updateFileDiagnostics :: MonadIO m
|
998 | 992 | updateFileDiagnostics fp k ShakeExtras{diagnostics, hiddenDiagnostics, publishedDiagnostics, state, debouncer, eventer} current = liftIO $ do
|
999 | 993 | modTime <- (currentValue =<<) <$> getValues state GetModificationTime fp
|
1000 | 994 | 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') |
1001 | 1001 | mask_ $ do
|
1002 | 1002 | -- Mask async exceptions to ensure that updated diagnostics are always
|
1003 | 1003 | -- published. Otherwise, we might never publish certain diagnostics if
|
1004 | 1004 | -- an exception strikes between modifyVar but before
|
1005 | 1005 | -- 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 |
1020 | 1008 | let uri = filePathToUri' fp
|
1021 | 1009 | let delay = if null newDiags then 0.1 else 0
|
1022 | 1010 | registerEvent debouncer delay uri $ do
|
@@ -1051,77 +1039,45 @@ actionLogger = do
|
1051 | 1039 | return logger
|
1052 | 1040 |
|
1053 | 1041 |
|
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 |
| - |
1093 | 1042 | getDiagnosticsFromStore :: StoreItem -> [Diagnostic]
|
1094 | 1043 | getDiagnosticsFromStore (StoreItem _ diags) = concatMap SL.fromSortedList $ Map.elems diags
|
1095 | 1044 |
|
1096 | 1045 |
|
1097 | 1046 | -- | Sets the diagnostics for a file and compilation step
|
1098 | 1047 | -- if you want to clear the diagnostics call this with an empty list
|
1099 | 1048 | setStageDiagnostics
|
1100 |
| - :: NormalizedFilePath |
| 1049 | + :: NormalizedUri |
1101 | 1050 | -> TextDocumentVersion -- ^ the time that the file these diagnostics originate from was last edited
|
1102 | 1051 | -> T.Text
|
1103 | 1052 | -> [LSP.Diagnostic]
|
1104 | 1053 | -> DiagnosticStore
|
1105 | 1054 | -> 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 | + |
1111 | 1067 |
|
1112 | 1068 | getAllDiagnostics ::
|
1113 | 1069 | DiagnosticStore ->
|
1114 | 1070 | [FileDiagnostic]
|
1115 | 1071 | getAllDiagnostics =
|
1116 | 1072 | concatMap (\(k,v) -> map (fromUri k,ShowDiag,) $ getDiagnosticsFromStore v) . HMap.toList
|
1117 | 1073 |
|
1118 |
| -getFileDiagnostics :: |
1119 |
| - NormalizedFilePath -> |
| 1074 | +getUriDiagnostics :: |
| 1075 | + NormalizedUri -> |
1120 | 1076 | DiagnosticStore ->
|
1121 | 1077 | [LSP.Diagnostic]
|
1122 |
| -getFileDiagnostics fp ds = |
| 1078 | +getUriDiagnostics uri ds = |
1123 | 1079 | maybe [] getDiagnosticsFromStore $
|
1124 |
| - HMap.lookup (filePathToUri' fp) ds |
| 1080 | + HMap.lookup uri ds |
1125 | 1081 |
|
1126 | 1082 | filterDiagnostics ::
|
1127 | 1083 | (NormalizedFilePath -> Bool) ->
|
|
0 commit comments