@@ -82,7 +82,7 @@ import Control.Concurrent.STM.Stats (atomicallyNamed)
8282import Control.Concurrent.Strict
8383import Control.DeepSeq
8484import Control.Exception.Extra hiding (bracket_ )
85- import Control.Lens ((&) , (?~) , (%~) )
85+ import Control.Lens ((&) , (?~) , (%~) , over )
8686import Control.Monad.Extra
8787import Control.Monad.IO.Class
8888import Control.Monad.Reader
@@ -120,6 +120,8 @@ import Data.Vector (Vector)
120120import qualified Data.Vector as Vector
121121import Development.IDE.Core.Debouncer
122122import Development.IDE.Core.FileUtils (getModTime )
123+ import Development.IDE.Core.HaskellErrorIndex hiding (Log )
124+ import qualified Development.IDE.Core.HaskellErrorIndex as HaskellErrorIndex
123125import Development.IDE.Core.PositionMapping
124126import Development.IDE.Core.ProgressReporting
125127import Development.IDE.Core.RuleTypes
@@ -151,6 +153,7 @@ import Development.IDE.Types.Shake
151153import qualified Focus
152154import GHC.Fingerprint
153155import GHC.Stack (HasCallStack )
156+ import GHC.Types.Error (diagnosticCode , errMsgDiagnostic )
154157import HieDb.Types
155158import Ide.Logger hiding (Priority )
156159import qualified Ide.Logger as Logger
@@ -194,6 +197,7 @@ data Log
194197 | LogShakeGarbageCollection ! T. Text ! Int ! Seconds
195198 -- * OfInterest Log messages
196199 | LogSetFilesOfInterest ! [(NormalizedFilePath , FileOfInterestStatus )]
200+ | LogInitializeHaskellErrorIndex ! HaskellErrorIndex. Log
197201 deriving Show
198202
199203instance Pretty Log where
@@ -237,6 +241,8 @@ instance Pretty Log where
237241 LogSetFilesOfInterest ofInterest ->
238242 " Set files of interst to" <> Pretty. line
239243 <> indent 4 (pretty $ fmap (first fromNormalizedFilePath) ofInterest)
244+ LogInitializeHaskellErrorIndex hei ->
245+ " Haskell Error Index:" <+> pretty hei
240246
241247-- | We need to serialize writes to the database, so we send any function that
242248-- needs to write to the database over the channel, where it will be picked up by
@@ -332,6 +338,8 @@ data ShakeExtras = ShakeExtras
332338 -- ^ Queue of restart actions to be run.
333339 , loaderQueue :: TQueue (IO () )
334340 -- ^ Queue of loader actions to be run.
341+ , haskellErrorIndex :: Maybe HaskellErrorIndex
342+ -- ^ List of errors in the Haskell Error Index (errors.haskell.org)
335343 }
336344
337345type WithProgressFunc = forall a .
@@ -702,6 +710,7 @@ shakeOpen recorder lspEnv defaultConfig idePlugins debouncer
702710 dirtyKeys <- newTVarIO mempty
703711 -- Take one VFS snapshot at the start
704712 vfsVar <- newTVarIO =<< vfsSnapshot lspEnv
713+ haskellErrorIndex <- initHaskellErrorIndex (cmapWithPrio LogInitializeHaskellErrorIndex recorder)
705714 pure ShakeExtras {shakeRecorder = recorder, .. }
706715 shakeDb <-
707716 shakeNewDatabase
@@ -1321,24 +1330,25 @@ traceA (A Failed{}) = "Failed"
13211330traceA (A Stale {}) = " Stale"
13221331traceA (A Succeeded {}) = " Success"
13231332
1324- updateFileDiagnostics :: MonadIO m
1325- => Recorder (WithPriority Log )
1333+ updateFileDiagnostics
1334+ :: Recorder (WithPriority Log )
13261335 -> NormalizedFilePath
13271336 -> Maybe Int32
13281337 -> Key
13291338 -> ShakeExtras
13301339 -> [FileDiagnostic ] -- ^ current results
1331- -> m ()
1340+ -> Action ()
13321341updateFileDiagnostics recorder fp ver k ShakeExtras {diagnostics, hiddenDiagnostics, publishedDiagnostics, debouncer, lspEnv, ideTesting} current0 = do
1342+ hei <- haskellErrorIndex <$> getShakeExtras
13331343 liftIO $ withTrace (" update diagnostics " <> fromString(fromNormalizedFilePath fp)) $ \ addTag -> do
13341344 addTag " key" (show k)
1345+ current <- traverse (attachHEI hei) $ map (over fdLspDiagnosticL diagsFromRule) current0
13351346 let (currentShown, currentHidden) = partition ((== ShowDiag ) . fdShouldShowDiagnostic) current
13361347 uri = filePathToUri' fp
13371348 addTagUnsafe :: String -> String -> String -> a -> a
13381349 addTagUnsafe msg t x v = unsafePerformIO(addTag (msg <> t) x) `seq` v
13391350 update :: (forall a . String -> String -> a -> a ) -> [FileDiagnostic ] -> STMDiagnosticStore -> STM [FileDiagnostic ]
13401351 update addTagUnsafeMethod new store = addTagUnsafeMethod " count" (show $ Prelude. length new) $ setStageDiagnostics addTagUnsafeMethod uri ver (renderKey k) new store
1341- current = map (fdLspDiagnosticL %~ diagsFromRule) current0
13421352 addTag " version" (show ver)
13431353 mask_ $ do
13441354 -- Mask async exceptions to ensure that updated diagnostics are always
@@ -1362,6 +1372,18 @@ updateFileDiagnostics recorder fp ver k ShakeExtras{diagnostics, hiddenDiagnosti
13621372 LSP. PublishDiagnosticsParams (fromNormalizedUri uri') (fmap fromIntegral ver) (map fdLspDiagnostic newDiags)
13631373 return action
13641374 where
1375+ attachHEI :: Maybe HaskellErrorIndex -> FileDiagnostic -> IO FileDiagnostic
1376+ attachHEI mbHei diag
1377+ | Just hei <- mbHei
1378+ , SomeStructuredMessage msg <- fdStructuredMessage diag
1379+ , Just code <- diagnosticCode (errMsgDiagnostic msg)
1380+ , Just heiError <- hei `heiGetError` code
1381+ = pure $ diag & fdLspDiagnosticL %~ attachHeiErrorCodeDescription heiError
1382+ | otherwise
1383+ = do
1384+ writeFile " /home/dylan/attachHEI" (show mbHei <> " \n " <> show diag)
1385+ pure diag
1386+
13651387 diagsFromRule :: Diagnostic -> Diagnostic
13661388 diagsFromRule c@ Diagnostic {_range}
13671389 | coerce ideTesting = c & L. relatedInformation ?~
0 commit comments