Skip to content

Commit 14d6697

Browse files
dylan-thinnesJaro Reinders
authored and
Jaro Reinders
committed
Set CodeDescription from HaskellErrorIndex when available
1 parent a857b9e commit 14d6697

File tree

4 files changed

+119
-13
lines changed

4 files changed

+119
-13
lines changed

ghcide/ghcide.cabal

+2
Original file line numberDiff line numberDiff line change
@@ -83,6 +83,7 @@ library
8383
, hiedb ^>= 0.6.0.0
8484
, hls-graph == 2.9.0.1
8585
, hls-plugin-api == 2.9.0.1
86+
, http-conduit
8687
, implicit-hie >= 0.1.4.0 && < 0.1.5
8788
, lens
8889
, lens-aeson
@@ -135,6 +136,7 @@ library
135136
Development.IDE.Core.Debouncer
136137
Development.IDE.Core.FileStore
137138
Development.IDE.Core.FileUtils
139+
Development.IDE.Core.HaskellErrorIndex
138140
Development.IDE.Core.IdeConfiguration
139141
Development.IDE.Core.OfInterest
140142
Development.IDE.Core.PluginUtils
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,80 @@
1+
-- Retrieve the list of errors from the HaskellErrorIndex via its API
2+
module Development.IDE.Core.HaskellErrorIndex where
3+
4+
import Control.Exception (tryJust)
5+
import Data.Aeson (FromJSON (..), (.:), withObject)
6+
import qualified Data.Map as M
7+
import qualified Data.Text as T
8+
import Development.IDE.Types.Diagnostics
9+
import GHC.Types.Error (DiagnosticCode)
10+
import Ide.Logger (Recorder, Pretty (..), WithPriority, logWith, Priority (..), vcat)
11+
import Language.LSP.Protocol.Types (Uri (..), CodeDescription (..))
12+
import Network.HTTP.Simple (HttpException, JSONException, getResponseBody, httpJSON)
13+
14+
data Log
15+
= LogHaskellErrorIndexInitialized
16+
| LogHaskellErrorIndexJSONError JSONException
17+
| LogHaskellErrorIndexHTTPError HttpException
18+
deriving (Show)
19+
20+
instance Pretty Log where
21+
pretty = \case
22+
LogHaskellErrorIndexInitialized -> "Initialized Haskell Error Index from internet"
23+
LogHaskellErrorIndexJSONError err ->
24+
vcat
25+
[ "Failed to initialize Haskell Error Index due to a JSON error:"
26+
, pretty (show err)
27+
]
28+
LogHaskellErrorIndexHTTPError err ->
29+
vcat
30+
[ "Failed to initialize Haskell Error Index due to an HTTP error:"
31+
, pretty (show err)
32+
]
33+
34+
newtype HaskellErrorIndex = HaskellErrorIndex (M.Map T.Text HEIError)
35+
deriving (Show, Eq, Ord)
36+
37+
data HEIError = HEIError
38+
{ code :: T.Text
39+
, route :: T.Text
40+
}
41+
deriving (Show, Eq, Ord)
42+
43+
errorsToIndex :: [HEIError] -> HaskellErrorIndex
44+
errorsToIndex errs = HaskellErrorIndex $ M.fromList $ map (\err -> (code err, err)) errs
45+
46+
instance FromJSON HEIError where
47+
parseJSON =
48+
withObject "HEIError" $ \v ->
49+
HEIError
50+
<$> v .: "code"
51+
<*> v .: "route"
52+
53+
instance FromJSON HaskellErrorIndex where
54+
parseJSON = fmap errorsToIndex <$> parseJSON
55+
56+
initHaskellErrorIndex :: Recorder (WithPriority Log) -> IO (Maybe HaskellErrorIndex)
57+
initHaskellErrorIndex recorder = do
58+
res <- tryJust handleJSONError $ tryJust handleHttpError $ httpJSON "https://errors.haskell.org/api/errors.json"
59+
case res of
60+
Left jsonErr -> do
61+
logWith recorder Info (LogHaskellErrorIndexJSONError jsonErr)
62+
pure Nothing
63+
Right (Left httpErr) -> do
64+
logWith recorder Info (LogHaskellErrorIndexHTTPError httpErr)
65+
pure Nothing
66+
Right (Right res) -> pure $ Just (getResponseBody res)
67+
where
68+
handleJSONError :: JSONException -> Maybe JSONException
69+
handleJSONError = Just
70+
handleHttpError :: HttpException -> Maybe HttpException
71+
handleHttpError = Just
72+
73+
heiGetError :: HaskellErrorIndex -> DiagnosticCode -> Maybe HEIError
74+
heiGetError (HaskellErrorIndex index) code = showGhcCode code `M.lookup` index
75+
76+
attachHeiErrorCodeDescription :: HEIError -> Diagnostic -> Diagnostic
77+
attachHeiErrorCodeDescription heiError diag =
78+
diag
79+
{ _codeDescription = Just $ CodeDescription $ Uri $ "https://errors.haskell.org/" <> route heiError
80+
}

ghcide/src/Development/IDE/Core/Shake.hs

+27-5
Original file line numberDiff line numberDiff line change
@@ -83,7 +83,7 @@ import Control.Concurrent.STM.Stats (atomicallyNamed)
8383
import Control.Concurrent.Strict
8484
import Control.DeepSeq
8585
import Control.Exception.Extra hiding (bracket_)
86-
import Control.Lens ((&), (?~), (%~))
86+
import Control.Lens ((&), (?~), (%~), over)
8787
import Control.Monad.Extra
8888
import Control.Monad.IO.Class
8989
import Control.Monad.Reader
@@ -121,6 +121,8 @@ import Data.Vector (Vector)
121121
import qualified Data.Vector as Vector
122122
import Development.IDE.Core.Debouncer
123123
import Development.IDE.Core.FileUtils (getModTime)
124+
import Development.IDE.Core.HaskellErrorIndex hiding (Log)
125+
import qualified Development.IDE.Core.HaskellErrorIndex as HaskellErrorIndex
124126
import Development.IDE.Core.PositionMapping
125127
import Development.IDE.Core.ProgressReporting
126128
import Development.IDE.Core.RuleTypes
@@ -156,6 +158,7 @@ import Development.IDE.Types.Shake
156158
import qualified Focus
157159
import GHC.Fingerprint
158160
import GHC.Stack (HasCallStack)
161+
import GHC.Types.Error (diagnosticCode, errMsgDiagnostic)
159162
import GHC.TypeLits (KnownSymbol)
160163
import HieDb.Types
161164
import 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

200204
instance 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

338346
type 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"
13231332
traceA (A Stale{}) = "Stale"
13241333
traceA (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 ()
13341343
updateFileDiagnostics 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 ?~

ghcide/src/Development/IDE/Types/Diagnostics.hs

+10-8
Original file line numberDiff line numberDiff line change
@@ -19,6 +19,7 @@ module Development.IDE.Types.Diagnostics (
1919
ideErrorFromLspDiag,
2020
showDiagnostics,
2121
showDiagnosticsColored,
22+
showGhcCode,
2223
IdeResultNoDiagnosticsEarlyCutoff,
2324
attachReason,
2425
attachedReason) where
@@ -77,19 +78,20 @@ ideErrorFromLspDiag lspDiag fdFilePath origMsg =
7778
Just msg -> SomeStructuredMessage msg
7879
fdLspDiagnostic = (attachReason (fmap (diagnosticReason . errMsgDiagnostic) origMsg) lspDiag)
7980
#if MIN_VERSION_ghc(9,6,1)
80-
{ _code = fmap ghcCodeToLspCode . diagnosticCode . errMsgDiagnostic =<< origMsg
81+
{ _code = fmap (InR . showGhcCode) . diagnosticCode . errMsgDiagnostic =<< origMsg
8182
}
8283
#endif
84+
in
85+
FileDiagnostic {..}
86+
8387
#if MIN_VERSION_ghc(9,8,1)
84-
ghcCodeToLspCode :: DiagnosticCode -> Int32 LSP.|? T.Text
85-
ghcCodeToLspCode = InR . T.pack . show
88+
showGhcCode :: DiagnosticCode -> T.Text
89+
showGhcCode = T.pack . show
8690
#elif MIN_VERSION_ghc(9,6,1)
87-
-- DiagnosticCode only got a show instance in 9.8.1
88-
ghcCodeToLspCode :: DiagnosticCode -> Int32 LSP.|? T.Text
89-
ghcCodeToLspCode (DiagnosticCode prefix c) = InR $ T.pack $ prefix ++ "-" ++ printf "%05d" c
91+
-- DiagnosticCode only got a show instance in 9.8.1
92+
showGhcCode :: DiagnosticCode -> T.Text
93+
showGhcCode (DiagnosticCode prefix c) = T.pack $ prefix ++ "-" ++ printf "%05d" c
9094
#endif
91-
in
92-
FileDiagnostic {..}
9395

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

0 commit comments

Comments
 (0)