@@ -83,7 +83,7 @@ import Control.Concurrent.STM.Stats (atomicallyNamed)
83
83
import Control.Concurrent.Strict
84
84
import Control.DeepSeq
85
85
import Control.Exception.Extra hiding (bracket_ )
86
- import Control.Lens ((&) , (?~) , (%~) )
86
+ import Control.Lens ((&) , (?~) , (%~) , over )
87
87
import Control.Monad.Extra
88
88
import Control.Monad.IO.Class
89
89
import Control.Monad.Reader
@@ -121,6 +121,8 @@ import Data.Vector (Vector)
121
121
import qualified Data.Vector as Vector
122
122
import Development.IDE.Core.Debouncer
123
123
import Development.IDE.Core.FileUtils (getModTime )
124
+ import Development.IDE.Core.HaskellErrorIndex hiding (Log )
125
+ import qualified Development.IDE.Core.HaskellErrorIndex as HaskellErrorIndex
124
126
import Development.IDE.Core.PositionMapping
125
127
import Development.IDE.Core.ProgressReporting
126
128
import Development.IDE.Core.RuleTypes
@@ -156,6 +158,7 @@ import Development.IDE.Types.Shake
156
158
import qualified Focus
157
159
import GHC.Fingerprint
158
160
import GHC.Stack (HasCallStack )
161
+ import GHC.Types.Error (diagnosticCode , errMsgDiagnostic )
159
162
import GHC.TypeLits (KnownSymbol )
160
163
import HieDb.Types
161
164
import Ide.Logger hiding (Priority )
@@ -195,6 +198,7 @@ data Log
195
198
| LogShakeGarbageCollection ! T. Text ! Int ! Seconds
196
199
-- * OfInterest Log messages
197
200
| LogSetFilesOfInterest ! [(NormalizedFilePath , FileOfInterestStatus )]
201
+ | LogInitializeHaskellErrorIndex ! HaskellErrorIndex. Log
198
202
deriving Show
199
203
200
204
instance Pretty Log where
@@ -238,6 +242,8 @@ instance Pretty Log where
238
242
LogSetFilesOfInterest ofInterest ->
239
243
" Set files of interst to" <> Pretty. line
240
244
<> indent 4 (pretty $ fmap (first fromNormalizedFilePath) ofInterest)
245
+ LogInitializeHaskellErrorIndex hei ->
246
+ " Haskell Error Index:" <+> pretty hei
241
247
242
248
-- | We need to serialize writes to the database, so we send any function that
243
249
-- needs to write to the database over the channel, where it will be picked up by
@@ -333,6 +339,8 @@ data ShakeExtras = ShakeExtras
333
339
-- ^ Queue of restart actions to be run.
334
340
, loaderQueue :: TQueue (IO () )
335
341
-- ^ Queue of loader actions to be run.
342
+ , haskellErrorIndex :: Maybe HaskellErrorIndex
343
+ -- ^ List of errors in the Haskell Error Index (errors.haskell.org)
336
344
}
337
345
338
346
type WithProgressFunc = forall a .
@@ -703,6 +711,7 @@ shakeOpen recorder lspEnv defaultConfig idePlugins debouncer
703
711
dirtyKeys <- newTVarIO mempty
704
712
-- Take one VFS snapshot at the start
705
713
vfsVar <- newTVarIO =<< vfsSnapshot lspEnv
714
+ haskellErrorIndex <- initHaskellErrorIndex (cmapWithPrio LogInitializeHaskellErrorIndex recorder)
706
715
pure ShakeExtras {shakeRecorder = recorder, .. }
707
716
shakeDb <-
708
717
shakeNewDatabase
@@ -1323,24 +1332,25 @@ traceA (A Failed{}) = "Failed"
1323
1332
traceA (A Stale {}) = " Stale"
1324
1333
traceA (A Succeeded {}) = " Success"
1325
1334
1326
- updateFileDiagnostics :: MonadIO m
1327
- => Recorder (WithPriority Log )
1335
+ updateFileDiagnostics
1336
+ :: Recorder (WithPriority Log )
1328
1337
-> NormalizedFilePath
1329
1338
-> Maybe Int32
1330
1339
-> Key
1331
1340
-> ShakeExtras
1332
1341
-> [FileDiagnostic ] -- ^ current results
1333
- -> m ()
1342
+ -> Action ()
1334
1343
updateFileDiagnostics recorder fp ver k ShakeExtras {diagnostics, hiddenDiagnostics, publishedDiagnostics, debouncer, lspEnv, ideTesting} current0 = do
1344
+ hei <- haskellErrorIndex <$> getShakeExtras
1335
1345
liftIO $ withTrace (" update diagnostics " <> fromString(fromNormalizedFilePath fp)) $ \ addTag -> do
1336
1346
addTag " key" (show k)
1347
+ current <- traverse (attachHEI hei) $ map (over fdLspDiagnosticL diagsFromRule) current0
1337
1348
let (currentShown, currentHidden) = partition ((== ShowDiag ) . fdShouldShowDiagnostic) current
1338
1349
uri = filePathToUri' fp
1339
1350
addTagUnsafe :: String -> String -> String -> a -> a
1340
1351
addTagUnsafe msg t x v = unsafePerformIO(addTag (msg <> t) x) `seq` v
1341
1352
update :: (forall a . String -> String -> a -> a ) -> [FileDiagnostic ] -> STMDiagnosticStore -> STM [FileDiagnostic ]
1342
1353
update addTagUnsafeMethod new store = addTagUnsafeMethod " count" (show $ Prelude. length new) $ setStageDiagnostics addTagUnsafeMethod uri ver (renderKey k) new store
1343
- current = map (fdLspDiagnosticL %~ diagsFromRule) current0
1344
1354
addTag " version" (show ver)
1345
1355
mask_ $ do
1346
1356
-- Mask async exceptions to ensure that updated diagnostics are always
@@ -1364,6 +1374,18 @@ updateFileDiagnostics recorder fp ver k ShakeExtras{diagnostics, hiddenDiagnosti
1364
1374
LSP. PublishDiagnosticsParams (fromNormalizedUri uri') (fmap fromIntegral ver) (map fdLspDiagnostic newDiags)
1365
1375
return action
1366
1376
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
+
1367
1389
diagsFromRule :: Diagnostic -> Diagnostic
1368
1390
diagsFromRule c@ Diagnostic {_range}
1369
1391
| coerce ideTesting = c & L. relatedInformation ?~
0 commit comments