@@ -178,7 +178,7 @@ import System.Time.Extra
178178data Log
179179 = LogCreateHieDbExportsMapStart
180180 | LogCreateHieDbExportsMapFinish ! Int
181- | LogBuildSessionRestart ! String ! [DelayedActionInternal ] ! (HashSet Key ) ! Seconds ! (Maybe FilePath )
181+ | LogBuildSessionRestart ! String ! [DelayedActionInternal ] ! (KeySet ) ! Seconds ! (Maybe FilePath )
182182 | LogBuildSessionRestartTakingTooLong ! Seconds
183183 | LogDelayedAction ! (DelayedAction () ) ! Seconds
184184 | LogBuildSessionFinish ! (Maybe SomeException )
@@ -197,7 +197,7 @@ instance Pretty Log where
197197 vcat
198198 [ " Restarting build session due to" <+> pretty reason
199199 , " Action Queue:" <+> pretty (map actionName actionQueue)
200- , " Keys:" <+> pretty (map show $ HSet. toList keyBackLog)
200+ , " Keys:" <+> pretty (map show $ toListKeySet keyBackLog)
201201 , " Aborting previous build session took" <+> pretty (showDuration abortDuration) <+> pretty shakeProfilePath ]
202202 LogBuildSessionRestartTakingTooLong seconds ->
203203 " Build restart is taking too long (" <> pretty seconds <> " seconds)"
@@ -279,7 +279,7 @@ data ShakeExtras = ShakeExtras
279279 ,clientCapabilities :: ClientCapabilities
280280 , withHieDb :: WithHieDb -- ^ Use only to read.
281281 , hiedbWriter :: HieDbWriter -- ^ use to write
282- , persistentKeys :: TVar (HMap. HashMap Key GetStalePersistent )
282+ , persistentKeys :: TVar (KeyMap GetStalePersistent )
283283 -- ^ Registery for functions that compute/get "stale" results for the rule
284284 -- (possibly from disk)
285285 , vfsVar :: TVar VFS
@@ -290,7 +290,7 @@ data ShakeExtras = ShakeExtras
290290 -- We don't need a STM.Map because we never update individual keys ourselves.
291291 , defaultConfig :: Config
292292 -- ^ Default HLS config, only relevant if the client does not provide any Config
293- , dirtyKeys :: TVar ( HashSet Key )
293+ , dirtyKeys :: TVar KeySet
294294 -- ^ Set of dirty rule keys since the last Shake run
295295 }
296296
@@ -324,7 +324,7 @@ getPluginConfig plugin = do
324324addPersistentRule :: IdeRule k v => k -> (NormalizedFilePath -> IdeAction (Maybe (v ,PositionDelta ,TextDocumentVersion ))) -> Rules ()
325325addPersistentRule k getVal = do
326326 ShakeExtras {persistentKeys} <- getShakeExtrasRules
327- void $ liftIO $ atomically $ modifyTVar' persistentKeys $ HMap. insert ( Key k) (fmap (fmap (first3 toDyn)) . getVal)
327+ void $ liftIO $ atomically $ modifyTVar' persistentKeys $ insertKeyMap (newKey k) (fmap (fmap (first3 toDyn)) . getVal)
328328
329329class Typeable a => IsIdeGlobal a where
330330
@@ -399,7 +399,7 @@ lastValueIO s@ShakeExtras{positionMapping,persistentKeys,state} k file = do
399399 pmap <- readTVarIO persistentKeys
400400 mv <- runMaybeT $ do
401401 liftIO $ Logger. logDebug (logger s) $ T. pack $ " LOOKUP PERSISTENT FOR: " ++ show k
402- f <- MaybeT $ pure $ HMap. lookup ( Key k) pmap
402+ f <- MaybeT $ pure $ lookupKeyMap (newKey k) pmap
403403 (dv,del,ver) <- MaybeT $ runIdeAction " lastValueIO" s $ f file
404404 MaybeT $ pure $ (,del,ver) <$> fromDynamic dv
405405 case mv of
@@ -509,7 +509,7 @@ deleteValue
509509 -> STM ()
510510deleteValue ShakeExtras {dirtyKeys, state} key file = do
511511 STM. delete (toKey key file) state
512- modifyTVar' dirtyKeys $ HSet. insert (toKey key file)
512+ modifyTVar' dirtyKeys $ insertKeySet (toKey key file)
513513
514514recordDirtyKeys
515515 :: Shake. ShakeValue k
@@ -518,7 +518,7 @@ recordDirtyKeys
518518 -> [NormalizedFilePath ]
519519 -> STM (IO () )
520520recordDirtyKeys ShakeExtras {dirtyKeys} key file = do
521- modifyTVar' dirtyKeys $ \ x -> foldl' (flip HSet. insert ) x (toKey key <$> file)
521+ modifyTVar' dirtyKeys $ \ x -> foldl' (flip insertKeySet ) x (toKey key <$> file)
522522 return $ withEventTrace " recordDirtyKeys" $ \ addEvent -> do
523523 addEvent (fromString $ unlines $ " dirty " <> show key : map fromNormalizedFilePath file)
524524
@@ -594,7 +594,7 @@ shakeOpen recorder lspEnv defaultConfig idePlugins logger debouncer
594594 positionMapping <- STM. newIO
595595 knownTargetsVar <- newTVarIO $ hashed HMap. empty
596596 let restartShakeSession = shakeRestart recorder ideState
597- persistentKeys <- newTVarIO HMap. empty
597+ persistentKeys <- newTVarIO mempty
598598 indexPending <- newTVarIO HMap. empty
599599 indexCompleted <- newTVarIO 0
600600 indexProgressToken <- newVar Nothing
@@ -637,7 +637,7 @@ shakeOpen recorder lspEnv defaultConfig idePlugins logger debouncer
637637
638638 -- monitoring
639639 let readValuesCounter = fromIntegral . countRelevantKeys checkParents <$> getStateKeys shakeExtras
640- readDirtyKeys = fromIntegral . countRelevantKeys checkParents . HSet. toList <$> readTVarIO(dirtyKeys shakeExtras)
640+ readDirtyKeys = fromIntegral . countRelevantKeys checkParents . toListKeySet <$> readTVarIO(dirtyKeys shakeExtras)
641641 readIndexPending = fromIntegral . HMap. size <$> readTVarIO (indexPending $ hiedbWriter shakeExtras)
642642 readExportsMap = fromIntegral . HMap. size . getExportsMap <$> readTVarIO (exportsMap shakeExtras)
643643 readDatabaseCount = fromIntegral . countRelevantKeys checkParents . map fst <$> shakeGetDatabaseKeys shakeDb
@@ -797,10 +797,10 @@ newSession recorder extras@ShakeExtras{..} vfsMod shakeDb acts reason = do
797797 workRun restore = withSpan " Shake session" $ \ otSpan -> do
798798 setTag otSpan " reason" (fromString reason)
799799 setTag otSpan " queue" (fromString $ unlines $ map actionName reenqueued)
800- whenJust allPendingKeys $ \ kk -> setTag otSpan " keys" (BS8. pack $ unlines $ map show $ toList kk)
800+ whenJust allPendingKeys $ \ kk -> setTag otSpan " keys" (BS8. pack $ unlines $ map show $ toListKeySet kk)
801801 let keysActs = pumpActionThread otSpan : map (run otSpan) (reenqueued ++ acts)
802802 res <- try @ SomeException $
803- restore $ shakeRunDatabaseForKeys (HSet. toList <$> allPendingKeys) shakeDb keysActs
803+ restore $ shakeRunDatabaseForKeys (toListKeySet <$> allPendingKeys) shakeDb keysActs
804804 return $ do
805805 let exception =
806806 case res of
@@ -890,7 +890,7 @@ garbageCollectKeys label maxAge checkParents agedKeys = do
890890 = atomicallyNamed " GC" $ do
891891 gotIt <- STM. focus (Focus. member <* Focus. delete) k values
892892 when gotIt $
893- modifyTVar' dk (HSet. insert k)
893+ modifyTVar' dk (insertKeySet k)
894894 return $ if gotIt then (counter+ 1 , k: keys) else st
895895 | otherwise = pure st
896896
@@ -1068,7 +1068,7 @@ defineEarlyCutoff recorder (Rule op) = addRule $ \(Q (key, file)) (old :: Maybe
10681068 extras <- getShakeExtras
10691069 let diagnostics ver diags = do
10701070 traceDiagnostics diags
1071- updateFileDiagnostics recorder file ver (Key key) extras . map (\ (_,y,z) -> (y,z)) $ diags
1071+ updateFileDiagnostics recorder file ver (newKey key) extras . map (\ (_,y,z) -> (y,z)) $ diags
10721072 defineEarlyCutoff' diagnostics (==) key file old mode $ const $ op key file
10731073defineEarlyCutoff recorder (RuleNoDiagnostics op) = addRule $ \ (Q (key, file)) (old :: Maybe BS. ByteString ) mode -> otTracedAction key file mode traceA $ \ traceDiagnostics -> do
10741074 let diagnostics _ver diags = do
@@ -1087,7 +1087,7 @@ defineEarlyCutoff recorder (RuleWithOldValue op) = addRule $ \(Q (key, file)) (o
10871087 extras <- getShakeExtras
10881088 let diagnostics ver diags = do
10891089 traceDiagnostics diags
1090- updateFileDiagnostics recorder file ver (Key key) extras . map (\ (_,y,z) -> (y,z)) $ diags
1090+ updateFileDiagnostics recorder file ver (newKey key) extras . map (\ (_,y,z) -> (y,z)) $ diags
10911091 defineEarlyCutoff' diagnostics (==) key file old mode $ op key file
10921092
10931093defineNoFile :: IdeRule k v => Recorder (WithPriority Log ) -> (k -> Action v ) -> Rules ()
@@ -1160,7 +1160,7 @@ defineEarlyCutoff' doDiagnostics cmp key file old mode action = do
11601160 (if eq then ChangedRecomputeSame else ChangedRecomputeDiff )
11611161 (encodeShakeValue bs) $
11621162 A res
1163- liftIO $ atomicallyNamed " define - dirtyKeys" $ modifyTVar' dirtyKeys (HSet. delete $ toKey key file)
1163+ liftIO $ atomicallyNamed " define - dirtyKeys" $ modifyTVar' dirtyKeys (deleteKeySet $ toKey key file)
11641164 return res
11651165 where
11661166 -- Highly unsafe helper to compute the version of a file
@@ -1199,15 +1199,16 @@ updateFileDiagnostics :: MonadIO m
11991199 -> ShakeExtras
12001200 -> [(ShowDiagnostic ,Diagnostic )] -- ^ current results
12011201 -> m ()
1202- updateFileDiagnostics recorder fp ver k ShakeExtras {diagnostics, hiddenDiagnostics, publishedDiagnostics, debouncer, lspEnv} current =
1202+ updateFileDiagnostics recorder fp ver k ShakeExtras {diagnostics, hiddenDiagnostics, publishedDiagnostics, debouncer, lspEnv, ideTesting} current0 =
12031203 liftIO $ withTrace (" update diagnostics " <> fromString(fromNormalizedFilePath fp)) $ \ addTag -> do
12041204 addTag " key" (show k)
12051205 let (currentShown, currentHidden) = partition ((== ShowDiag ) . fst ) current
12061206 uri = filePathToUri' fp
12071207 addTagUnsafe :: String -> String -> String -> a -> a
12081208 addTagUnsafe msg t x v = unsafePerformIO(addTag (msg <> t) x) `seq` v
12091209 update :: (forall a . String -> String -> a -> a ) -> [Diagnostic ] -> STMDiagnosticStore -> STM [Diagnostic ]
1210- update addTagUnsafe new store = addTagUnsafe " count" (show $ Prelude. length new) $ setStageDiagnostics addTagUnsafe uri ver (T. pack $ show k) new store
1210+ update addTagUnsafe new store = addTagUnsafe " count" (show $ Prelude. length new) $ setStageDiagnostics addTagUnsafe uri ver (renderKey k) new store
1211+ current = second diagsFromRule <$> current0
12111212 addTag " version" (show ver)
12121213 mask_ $ do
12131214 -- Mask async exceptions to ensure that updated diagnostics are always
@@ -1230,6 +1231,22 @@ updateFileDiagnostics recorder fp ver k ShakeExtras{diagnostics, hiddenDiagnosti
12301231 LSP. sendNotification LSP. STextDocumentPublishDiagnostics $
12311232 LSP. PublishDiagnosticsParams (fromNormalizedUri uri) (fmap fromIntegral ver) (List newDiags)
12321233 return action
1234+ where
1235+ diagsFromRule :: Diagnostic -> Diagnostic
1236+ diagsFromRule c@ Diagnostic {_range}
1237+ | coerce ideTesting = c
1238+ {_relatedInformation =
1239+ Just $ List [
1240+ DiagnosticRelatedInformation
1241+ (Location
1242+ (filePathToUri $ fromNormalizedFilePath fp)
1243+ _range
1244+ )
1245+ (T. pack $ show k)
1246+ ]
1247+ }
1248+ | otherwise = c
1249+
12331250
12341251newtype Priority = Priority Double
12351252
0 commit comments