@@ -83,7 +83,7 @@ import Control.Concurrent.STM.Stats (atomicallyNamed)
8383import Control.Concurrent.Strict
8484import Control.DeepSeq
8585import Control.Exception.Extra hiding (bracket_ )
86- import Control.Lens ((&) , (?~) , (%~) )
86+ import Control.Lens ((&) , (?~) , (%~) , over )
8787import Control.Monad.Extra
8888import Control.Monad.IO.Class
8989import Control.Monad.Reader
@@ -121,6 +121,8 @@ import Data.Vector (Vector)
121121import qualified Data.Vector as Vector
122122import Development.IDE.Core.Debouncer
123123import Development.IDE.Core.FileUtils (getModTime )
124+ import Development.IDE.Core.HaskellErrorIndex hiding (Log )
125+ import qualified Development.IDE.Core.HaskellErrorIndex as HaskellErrorIndex
124126import Development.IDE.Core.PositionMapping
125127import Development.IDE.Core.ProgressReporting
126128import Development.IDE.Core.RuleTypes
@@ -156,6 +158,7 @@ import Development.IDE.Types.Shake
156158import qualified Focus
157159import GHC.Fingerprint
158160import GHC.Stack (HasCallStack )
161+ import GHC.Types.Error (diagnosticCode , errMsgDiagnostic )
159162import GHC.TypeLits (KnownSymbol )
160163import HieDb.Types
161164import Ide.Logger hiding (Priority )
@@ -195,6 +198,7 @@ data Log
195198 | LogShakeGarbageCollection ! T. Text ! Int ! Seconds
196199 -- * OfInterest Log messages
197200 | LogSetFilesOfInterest ! [(NormalizedFilePath , FileOfInterestStatus )]
201+ | LogInitializeHaskellErrorIndex ! HaskellErrorIndex. Log
198202 deriving Show
199203
200204instance Pretty Log where
@@ -238,6 +242,8 @@ instance Pretty Log where
238242 LogSetFilesOfInterest ofInterest ->
239243 " Set files of interst to" <> Pretty. line
240244 <> indent 4 (pretty $ fmap (first fromNormalizedFilePath) ofInterest)
245+ LogInitializeHaskellErrorIndex hei ->
246+ " Haskell Error Index:" <+> pretty hei
241247
242248-- | We need to serialize writes to the database, so we send any function that
243249-- needs to write to the database over the channel, where it will be picked up by
@@ -333,6 +339,8 @@ data ShakeExtras = ShakeExtras
333339 -- ^ Queue of restart actions to be run.
334340 , loaderQueue :: TQueue (IO () )
335341 -- ^ Queue of loader actions to be run.
342+ , haskellErrorIndex :: Maybe HaskellErrorIndex
343+ -- ^ List of errors in the Haskell Error Index (errors.haskell.org)
336344 }
337345
338346type WithProgressFunc = forall a .
@@ -703,6 +711,7 @@ shakeOpen recorder lspEnv defaultConfig idePlugins debouncer
703711 dirtyKeys <- newTVarIO mempty
704712 -- Take one VFS snapshot at the start
705713 vfsVar <- newTVarIO =<< vfsSnapshot lspEnv
714+ haskellErrorIndex <- initHaskellErrorIndex (cmapWithPrio LogInitializeHaskellErrorIndex recorder)
706715 pure ShakeExtras {shakeRecorder = recorder, .. }
707716 shakeDb <-
708717 shakeNewDatabase
@@ -1323,24 +1332,25 @@ traceA (A Failed{}) = "Failed"
13231332traceA (A Stale {}) = " Stale"
13241333traceA (A Succeeded {}) = " Success"
13251334
1326- updateFileDiagnostics :: MonadIO m
1327- => Recorder (WithPriority Log )
1335+ updateFileDiagnostics
1336+ :: Recorder (WithPriority Log )
13281337 -> NormalizedFilePath
13291338 -> Maybe Int32
13301339 -> Key
13311340 -> ShakeExtras
13321341 -> [FileDiagnostic ] -- ^ current results
1333- -> m ()
1342+ -> Action ()
13341343updateFileDiagnostics recorder fp ver k ShakeExtras {diagnostics, hiddenDiagnostics, publishedDiagnostics, debouncer, lspEnv, ideTesting} current0 = do
1344+ hei <- haskellErrorIndex <$> getShakeExtras
13351345 liftIO $ withTrace (" update diagnostics " <> fromString(fromNormalizedFilePath fp)) $ \ addTag -> do
13361346 addTag " key" (show k)
1347+ current <- traverse (attachHEI hei) $ map (over fdLspDiagnosticL diagsFromRule) current0
13371348 let (currentShown, currentHidden) = partition ((== ShowDiag ) . fdShouldShowDiagnostic) current
13381349 uri = filePathToUri' fp
13391350 addTagUnsafe :: String -> String -> String -> a -> a
13401351 addTagUnsafe msg t x v = unsafePerformIO(addTag (msg <> t) x) `seq` v
13411352 update :: (forall a . String -> String -> a -> a ) -> [FileDiagnostic ] -> STMDiagnosticStore -> STM [FileDiagnostic ]
13421353 update addTagUnsafeMethod new store = addTagUnsafeMethod " count" (show $ Prelude. length new) $ setStageDiagnostics addTagUnsafeMethod uri ver (renderKey k) new store
1343- current = map (fdLspDiagnosticL %~ diagsFromRule) current0
13441354 addTag " version" (show ver)
13451355 mask_ $ do
13461356 -- Mask async exceptions to ensure that updated diagnostics are always
@@ -1364,6 +1374,18 @@ updateFileDiagnostics recorder fp ver k ShakeExtras{diagnostics, hiddenDiagnosti
13641374 LSP. PublishDiagnosticsParams (fromNormalizedUri uri') (fmap fromIntegral ver) (map fdLspDiagnostic newDiags)
13651375 return action
13661376 where
1377+ attachHEI :: Maybe HaskellErrorIndex -> FileDiagnostic -> IO FileDiagnostic
1378+ attachHEI mbHei diag
1379+ | Just hei <- mbHei
1380+ , SomeStructuredMessage msg <- fdStructuredMessage diag
1381+ , Just code <- diagnosticCode (errMsgDiagnostic msg)
1382+ , Just heiError <- hei `heiGetError` code
1383+ = pure $ diag & fdLspDiagnosticL %~ attachHeiErrorCodeDescription heiError
1384+ | otherwise
1385+ = do
1386+ writeFile " /home/dylan/attachHEI" (show mbHei <> " \n " <> show diag)
1387+ pure diag
1388+
13671389 diagsFromRule :: Diagnostic -> Diagnostic
13681390 diagsFromRule c@ Diagnostic {_range}
13691391 | coerce ideTesting = c & L. relatedInformation ?~
0 commit comments