@@ -73,7 +73,8 @@ module Development.IDE.Core.Shake(
7373 garbageCollectDirtyKeysOlderThan ,
7474 Log (.. ),
7575 VFSModified (.. ), getClientConfigAction ,
76- ThreadQueue (.. )
76+ ThreadQueue (.. ),
77+ runWithSignal
7778 ) where
7879
7980import Control.Concurrent.Async
@@ -123,6 +124,10 @@ import Development.IDE.Core.FileUtils (getModTime)
123124import Development.IDE.Core.PositionMapping
124125import Development.IDE.Core.ProgressReporting
125126import Development.IDE.Core.RuleTypes
127+ import Development.IDE.Types.Options as Options
128+ import qualified Language.LSP.Protocol.Message as LSP
129+ import qualified Language.LSP.Server as LSP
130+
126131import Development.IDE.Core.Tracing
127132import Development.IDE.Core.WorkerThread
128133import Development.IDE.GHC.Compat (NameCache ,
@@ -147,11 +152,11 @@ import qualified Development.IDE.Types.Exports as ExportsMap
147152import Development.IDE.Types.KnownTargets
148153import Development.IDE.Types.Location
149154import Development.IDE.Types.Monitoring (Monitoring (.. ))
150- import Development.IDE.Types.Options
151155import Development.IDE.Types.Shake
152156import qualified Focus
153157import GHC.Fingerprint
154158import GHC.Stack (HasCallStack )
159+ import GHC.TypeLits (KnownSymbol )
155160import HieDb.Types
156161import Ide.Logger hiding (Priority )
157162import qualified Ide.Logger as Logger
@@ -165,7 +170,6 @@ import qualified Language.LSP.Protocol.Lens as L
165170import Language.LSP.Protocol.Message
166171import Language.LSP.Protocol.Types
167172import qualified Language.LSP.Protocol.Types as LSP
168- import qualified Language.LSP.Server as LSP
169173import Language.LSP.VFS hiding (start )
170174import qualified "list-t" ListT
171175import OpenTelemetry.Eventlog hiding (addEvent )
@@ -1350,29 +1354,28 @@ updateFileDiagnostics recorder fp ver k ShakeExtras{diagnostics, hiddenDiagnosti
13501354 let uri' = filePathToUri' fp
13511355 let delay = if null newDiags then 0.1 else 0
13521356 registerEvent debouncer delay uri' $ withTrace (" report diagnostics " <> fromString (fromNormalizedFilePath fp)) $ \ tag -> do
1353- join $ mask_ $ do
1354- lastPublish <- atomicallyNamed " diagnostics - publish" $ STM. focus (Focus. lookupWithDefault [] <* Focus. insert newDiags) uri' publishedDiagnostics
1355- let action = when (lastPublish /= newDiags) $ case lspEnv of
1357+ join $ mask_ $ do
1358+ lastPublish <- atomicallyNamed " diagnostics - publish" $ STM. focus (Focus. lookupWithDefault [] <* Focus. insert newDiags) uri' publishedDiagnostics
1359+ let action = when (lastPublish /= newDiags) $ case lspEnv of
13561360 Nothing -> -- Print an LSP event.
13571361 logWith recorder Info $ LogDiagsDiffButNoLspEnv (map (fp, ShowDiag ,) newDiags)
13581362 Just env -> LSP. runLspT env $ do
13591363 liftIO $ tag " count" (show $ Prelude. length newDiags)
13601364 liftIO $ tag " key" (show k)
13611365 LSP. sendNotification SMethod_TextDocumentPublishDiagnostics $
13621366 LSP. PublishDiagnosticsParams (fromNormalizedUri uri') (fmap fromIntegral ver) newDiags
1363- return action
1367+ return action
13641368 where
13651369 diagsFromRule :: Diagnostic -> Diagnostic
13661370 diagsFromRule c@ Diagnostic {_range}
13671371 | coerce ideTesting = c & L. relatedInformation ?~
1368- [
1369- DiagnosticRelatedInformation
1372+ [ DiagnosticRelatedInformation
13701373 (Location
13711374 (filePathToUri $ fromNormalizedFilePath fp)
13721375 _range
13731376 )
13741377 (T. pack $ show k)
1375- ]
1378+ ]
13761379 | otherwise = c
13771380
13781381
@@ -1444,3 +1447,19 @@ updatePositionMappingHelper ver changes mappingForUri = snd $
14441447 EM. mapAccumRWithKey (\ acc _k (delta, _) -> let new = addOldDelta delta acc in (new, (delta, acc)))
14451448 zeroMapping
14461449 (EM. insert ver (mkDelta changes, zeroMapping) mappingForUri)
1450+
1451+ -- | sends a signal whenever shake session is run/restarted
1452+ -- being used in cabal and hlint plugin tests to know when its time
1453+ -- to look for file diagnostics
1454+ kickSignal :: KnownSymbol s => Bool -> Maybe (LSP. LanguageContextEnv c ) -> [NormalizedFilePath ] -> Proxy s -> Action ()
1455+ kickSignal testing lspEnv files msg = when testing $ liftIO $ mRunLspT lspEnv $
1456+ LSP. sendNotification (LSP. SMethod_CustomMethod msg) $
1457+ toJSON $ map fromNormalizedFilePath files
1458+
1459+ -- | Add kick start/done signal to rule
1460+ runWithSignal :: (KnownSymbol s0 , KnownSymbol s1 , IdeRule k v ) => Proxy s0 -> Proxy s1 -> [NormalizedFilePath ] -> k -> Action ()
1461+ runWithSignal msgStart msgEnd files rule = do
1462+ ShakeExtras {ideTesting = Options. IdeTesting testing, lspEnv} <- getShakeExtras
1463+ kickSignal testing lspEnv files msgStart
1464+ void $ uses rule files
1465+ kickSignal testing lspEnv files msgEnd
0 commit comments