Skip to content

Commit

Permalink
Revert "Set CodeDescription from HaskellErrorIndex when available"
Browse files Browse the repository at this point in the history
This reverts commit 14d6697.
  • Loading branch information
noughtmare committed Oct 24, 2024
1 parent 1f835da commit 1bc221c
Show file tree
Hide file tree
Showing 4 changed files with 7 additions and 129 deletions.
2 changes: 0 additions & 2 deletions ghcide/ghcide.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -83,7 +83,6 @@ library
, hiedb ^>= 0.6.0.0
, hls-graph == 2.9.0.1
, hls-plugin-api == 2.9.0.1
, http-conduit
, implicit-hie >= 0.1.4.0 && < 0.1.5
, lens
, lens-aeson
Expand Down Expand Up @@ -136,7 +135,6 @@ library
Development.IDE.Core.Debouncer
Development.IDE.Core.FileStore
Development.IDE.Core.FileUtils
Development.IDE.Core.HaskellErrorIndex
Development.IDE.Core.IdeConfiguration
Development.IDE.Core.OfInterest
Development.IDE.Core.PluginUtils
Expand Down
104 changes: 0 additions & 104 deletions ghcide/src/Development/IDE/Core/HaskellErrorIndex.hs

This file was deleted.

28 changes: 5 additions & 23 deletions ghcide/src/Development/IDE/Core/Shake.hs
Original file line number Diff line number Diff line change
Expand Up @@ -83,7 +83,7 @@ import Control.Concurrent.STM.Stats (atomicallyNamed)
import Control.Concurrent.Strict
import Control.DeepSeq
import Control.Exception.Extra hiding (bracket_)
import Control.Lens (over, (%~), (&), (?~))
import Control.Lens ((&), (?~), (%~))
import Control.Monad.Extra
import Control.Monad.IO.Class
import Control.Monad.Reader
Expand Down Expand Up @@ -121,8 +121,6 @@ import Data.Vector (Vector)
import qualified Data.Vector as Vector
import Development.IDE.Core.Debouncer
import Development.IDE.Core.FileUtils (getModTime)
import Development.IDE.Core.HaskellErrorIndex hiding (Log)
import qualified Development.IDE.Core.HaskellErrorIndex as HaskellErrorIndex
import Development.IDE.Core.PositionMapping
import Development.IDE.Core.ProgressReporting
import Development.IDE.Core.RuleTypes
Expand Down Expand Up @@ -198,7 +196,6 @@ data Log
| LogShakeGarbageCollection !T.Text !Int !Seconds
-- * OfInterest Log messages
| LogSetFilesOfInterest ![(NormalizedFilePath, FileOfInterestStatus)]
| LogInitializeHaskellErrorIndex !HaskellErrorIndex.Log
deriving Show

instance Pretty Log where
Expand Down Expand Up @@ -242,8 +239,6 @@ instance Pretty Log where
LogSetFilesOfInterest ofInterest ->
"Set files of interst to" <> Pretty.line
<> indent 4 (pretty $ fmap (first fromNormalizedFilePath) ofInterest)
LogInitializeHaskellErrorIndex hei ->
"Haskell Error Index:" <+> pretty hei

-- | We need to serialize writes to the database, so we send any function that
-- needs to write to the database over the channel, where it will be picked up by
Expand Down Expand Up @@ -339,8 +334,6 @@ data ShakeExtras = ShakeExtras
-- ^ Queue of restart actions to be run.
, loaderQueue :: TQueue (IO ())
-- ^ Queue of loader actions to be run.
, haskellErrorIndex :: Maybe HaskellErrorIndex
-- ^ List of errors in the Haskell Error Index (errors.haskell.org)
}

type WithProgressFunc = forall a.
Expand Down Expand Up @@ -711,7 +704,6 @@ shakeOpen recorder lspEnv defaultConfig idePlugins debouncer
dirtyKeys <- newTVarIO mempty
-- Take one VFS snapshot at the start
vfsVar <- newTVarIO =<< vfsSnapshot lspEnv
haskellErrorIndex <- initHaskellErrorIndex (cmapWithPrio LogInitializeHaskellErrorIndex recorder)
pure ShakeExtras{shakeRecorder = recorder, ..}
shakeDb <-
shakeNewDatabase
Expand Down Expand Up @@ -1332,25 +1324,24 @@ traceA (A Failed{}) = "Failed"
traceA (A Stale{}) = "Stale"
traceA (A Succeeded{}) = "Success"

updateFileDiagnostics
:: Recorder (WithPriority Log)
updateFileDiagnostics :: MonadIO m
=> Recorder (WithPriority Log)
-> NormalizedFilePath
-> Maybe Int32
-> Key
-> ShakeExtras
-> [FileDiagnostic] -- ^ current results
-> Action ()
-> m ()
updateFileDiagnostics recorder fp ver k ShakeExtras{diagnostics, hiddenDiagnostics, publishedDiagnostics, debouncer, lspEnv, ideTesting} current0 = do
hei <- haskellErrorIndex <$> getShakeExtras
liftIO $ withTrace ("update diagnostics " <> fromString(fromNormalizedFilePath fp)) $ \ addTag -> do
addTag "key" (show k)
current <- traverse (attachHEI hei) $ map (over fdLspDiagnosticL diagsFromRule) current0
let (currentShown, currentHidden) = partition ((== ShowDiag) . fdShouldShowDiagnostic) current
uri = filePathToUri' fp
addTagUnsafe :: String -> String -> String -> a -> a
addTagUnsafe msg t x v = unsafePerformIO(addTag (msg <> t) x) `seq` v
update :: (forall a. String -> String -> a -> a) -> [FileDiagnostic] -> STMDiagnosticStore -> STM [FileDiagnostic]
update addTagUnsafeMethod new store = addTagUnsafeMethod "count" (show $ Prelude.length new) $ setStageDiagnostics addTagUnsafeMethod uri ver (renderKey k) new store
current = map (fdLspDiagnosticL %~ diagsFromRule) current0
addTag "version" (show ver)
mask_ $ do
-- Mask async exceptions to ensure that updated diagnostics are always
Expand All @@ -1374,15 +1365,6 @@ updateFileDiagnostics recorder fp ver k ShakeExtras{diagnostics, hiddenDiagnosti
LSP.PublishDiagnosticsParams (fromNormalizedUri uri') (fmap fromIntegral ver) (map fdLspDiagnostic newDiags)
return action
where
attachHEI :: Maybe HaskellErrorIndex -> FileDiagnostic -> IO FileDiagnostic
attachHEI mbHei diag
| Just hei <- mbHei
, SomeStructuredMessage msg <- fdStructuredMessage diag
, Just heiError <- hei `heiGetError` errMsgDiagnostic msg
= pure $ diag & fdLspDiagnosticL %~ attachHeiErrorCodeDescription heiError
| otherwise
= pure diag

diagsFromRule :: Diagnostic -> Diagnostic
diagsFromRule c@Diagnostic{_range}
| coerce ideTesting = c & L.relatedInformation ?~
Expand Down
2 changes: 2 additions & 0 deletions ghcide/src/Development/IDE/Types/Diagnostics.hs
Original file line number Diff line number Diff line change
Expand Up @@ -119,6 +119,8 @@ showGhcCode = T.pack . show
showGhcCode :: DiagnosticCode -> T.Text
showGhcCode (DiagnosticCode prefix c) = T.pack $ prefix ++ "-" ++ printf "%05d" c
#endif
in
FileDiagnostic {..}

attachedReason :: Traversal' Diagnostic (Maybe JSON.Value)
attachedReason = data_ . non (JSON.object []) . JSON.atKey "attachedReason"
Expand Down

0 comments on commit 1bc221c

Please sign in to comment.