Skip to content

Commit b2ea71d

Browse files
authored
Fix the Eval plugin sporadic exceptions (#1345)
* Fresh session for evaluation * Clean up redundant imports and identifiers
1 parent a49f366 commit b2ea71d

File tree

2 files changed

+41
-46
lines changed

2 files changed

+41
-46
lines changed

ghcide/ghcide.cabal

+1-1
Original file line numberDiff line numberDiff line change
@@ -151,6 +151,7 @@ library
151151
Development.IDE.Core.Shake
152152
Development.IDE.Core.Tracing
153153
Development.IDE.GHC.Compat
154+
Development.IDE.Core.Compile
154155
Development.IDE.GHC.Error
155156
Development.IDE.GHC.ExactPrint
156157
Development.IDE.GHC.Orphans
@@ -197,7 +198,6 @@ library
197198
other-modules:
198199
Development.IDE.Session.VersionCheck
199200
other-modules:
200-
Development.IDE.Core.Compile
201201
Development.IDE.Core.FileExists
202202
Development.IDE.GHC.CPP
203203
Development.IDE.GHC.Warnings

plugins/hls-eval-plugin/src/Ide/Plugin/Eval/CodeLens.hs

+40-45
Original file line numberDiff line numberDiff line change
@@ -36,13 +36,8 @@ import Control.Monad.IO.Class (MonadIO (liftIO))
3636
import Control.Monad.Trans.Except
3737
( ExceptT (..),
3838
)
39-
import Data.Aeson
40-
( FromJSON,
41-
ToJSON,
42-
toJSON,
43-
)
39+
import Data.Aeson (toJSON)
4440
import Data.Char (isSpace)
45-
import Data.Either (isRight)
4641
import qualified Data.HashMap.Strict as HashMap
4742
import Data.List
4843
(dropWhileEnd,
@@ -59,10 +54,10 @@ import qualified Data.Text as T
5954
import Data.Time (getCurrentTime)
6055
import Data.Typeable (Typeable)
6156
import Development.IDE
62-
(realSrcSpanToRange, GetModSummary (..),
57+
( Action,
58+
realSrcSpanToRange, GetModSummary (..),
6359
GetParsedModuleWithComments (..),
64-
GhcSession (..),
65-
HscEnvEq (envImportPaths),
60+
HscEnvEq,
6661
IdeState,
6762
List (List),
6863
NormalizedFilePath,
@@ -77,9 +72,15 @@ import Development.IDE
7772
toNormalizedUri,
7873
uriToFilePath',
7974
useWithStale_,
80-
use_, prettyPrint
75+
prettyPrint,
76+
use_, useNoFile_, uses_,
77+
GhcSessionIO(..), GetDependencies(..), GetModIface(..),
78+
HiFileResult (hirHomeMod, hirModSummary)
8179
)
80+
import Development.IDE.Core.Rules (TransitiveDependencies(transitiveModuleDeps))
81+
import Development.IDE.Core.Compile (setupFinderCache, loadModulesHome)
8282
import Development.IDE.GHC.Compat (AnnotationComment(AnnBlockComment, AnnLineComment), GenLocated (L), HscEnv, ParsedModule (..), SrcSpan (RealSrcSpan, UnhelpfulSpan), srcSpanFile, GhcException, setInteractiveDynFlags)
83+
import Development.IDE.Types.Options
8384
import DynamicLoading (initializePlugins)
8485
import FastString (unpackFS)
8586
import GHC
@@ -109,16 +110,14 @@ import GHC
109110
load,
110111
runDecls,
111112
setContext,
112-
setInteractiveDynFlags,
113113
setLogAction,
114114
setSessionDynFlags,
115115
setTargets,
116116
typeKind,
117117
)
118-
import GHC.Generics (Generic)
119-
import qualified GHC.LanguageExtensions.Type as LangExt
120118
import GhcPlugins
121119
( DynFlags (..),
120+
hsc_dflags,
122121
defaultLogActionHPutStrDoc,
123122
gopt_set,
124123
gopt_unset,
@@ -147,15 +146,14 @@ import Ide.Plugin.Eval.Code
147146
testRanges,
148147
)
149148
import Ide.Plugin.Eval.GHC
150-
( addExtension,
151-
addImport,
149+
( addImport,
152150
addPackages,
153151
hasPackage,
154152
isExpr,
155153
showDynFlags,
156154
)
157155
import Ide.Plugin.Eval.Parse.Comments (commentsToSections)
158-
import Ide.Plugin.Eval.Parse.Option (langOptions, parseSetFlags)
156+
import Ide.Plugin.Eval.Parse.Option (parseSetFlags)
159157
import Ide.Plugin.Eval.Types
160158
import Ide.Plugin.Eval.Util
161159
( asS,
@@ -214,7 +212,6 @@ import Outputable
214212
import System.FilePath (takeFileName)
215213
import System.IO (hClose)
216214
import System.IO.Temp (withSystemTempFile)
217-
import Text.Read (readMaybe)
218215
import Util (OverridingBool (Never))
219216
import Development.IDE.Core.PositionMapping (toCurrentRange)
220217
import qualified Data.DList as DL
@@ -344,14 +341,14 @@ runEvalCmd lsp st EvalParams{..} =
344341
(Just (textToStringBuffer mdlText, now))
345342

346343
-- Setup environment for evaluation
347-
hscEnv' <- withSystemTempFile (takeFileName fp) $ \logFilename logHandle -> ExceptT . (either Left id <$>) . gStrictTry . evalGhcEnv (hscEnvWithImportPaths session) $ do
344+
hscEnv' <- withSystemTempFile (takeFileName fp) $ \logFilename logHandle -> ExceptT . (either Left id <$>) . gStrictTry . evalGhcEnv session $ do
348345
env <- getSession
349346

350347
-- Install the module pragmas and options
351348
df <- liftIO $ setupDynFlagsForGHCiLike env $ ms_hspp_opts ms
352349

353-
let impPaths = fromMaybe (importPaths df) (envImportPaths session)
354-
-- Restore the cradle import paths
350+
-- Restore the original import paths
351+
let impPaths = importPaths $ hsc_dflags env
355352
df <- return df{importPaths = impPaths}
356353

357354
-- Set the modified flags in the session
@@ -640,14 +637,29 @@ prettyWarn Warn{..} =
640637
prettyPrint (SrcLoc.getLoc warnMsg) <> ": warning:\n"
641638
<> " " <> SrcLoc.unLoc warnMsg
642639

643-
runGetSession :: MonadIO m => IdeState -> NormalizedFilePath -> m HscEnvEq
644-
runGetSession st nfp =
645-
liftIO $
646-
runAction "getSession" st $
647-
use_
648-
GhcSession
649-
-- GhcSessionDeps
650-
nfp
640+
ghcSessionDepsDefinition :: HscEnvEq -> NormalizedFilePath -> Action HscEnv
641+
ghcSessionDepsDefinition env file = do
642+
let hsc = hscEnvWithImportPaths env
643+
deps <- use_ GetDependencies file
644+
let tdeps = transitiveModuleDeps deps
645+
ifaces <- uses_ GetModIface tdeps
646+
647+
-- Currently GetDependencies returns things in topological order so A comes before B if A imports B.
648+
-- We need to reverse this as GHC gets very unhappy otherwise and complains about broken interfaces.
649+
-- Long-term we might just want to change the order returned by GetDependencies
650+
let inLoadOrder = reverse (map hirHomeMod ifaces)
651+
652+
liftIO $ loadModulesHome inLoadOrder <$> setupFinderCache (map hirModSummary ifaces) hsc
653+
654+
runGetSession :: MonadIO m => IdeState -> NormalizedFilePath -> m HscEnv
655+
runGetSession st nfp = liftIO $ runAction "eval" st $ do
656+
-- Create a new GHC Session rather than reusing an existing one
657+
-- to avoid interfering with ghcide
658+
IdeGhcSession{loadSessionFun} <- useNoFile_ GhcSessionIO
659+
let fp = fromNormalizedFilePath nfp
660+
((_, res),_) <- liftIO $ loadSessionFun fp
661+
let hscEnv = fromMaybe (error $ "Unknown file: " <> fp) res
662+
ghcSessionDepsDefinition hscEnv nfp
651663

652664
needsQuickCheck :: [(Section, Test)] -> Bool
653665
needsQuickCheck = any (isProperty . snd)
@@ -670,23 +682,6 @@ errorLines =
670682
. T.lines
671683
. T.pack
672684

673-
{-
674-
Check that extensions actually exists.
675-
676-
>>> ghcOptions ":set -XLambdaCase"
677-
Right [LambdaCase]
678-
>>> ghcOptions ":set -XLambdaCase -XNotRight"
679-
Left "Unknown extension: \"NotRight\""
680-
-}
681-
ghcOptions :: [Char] -> Either String [LangExt.Extension]
682-
ghcOptions = either Left (mapM chk) . langOptions
683-
where
684-
chk o =
685-
maybe
686-
(Left $ unwords ["Unknown extension:", show o])
687-
Right
688-
(readMaybe o :: Maybe LangExt.Extension)
689-
690685
{- |
691686
>>> map (pad_ (T.pack "--")) (map T.pack ["2+2",""])
692687
["--2+2","--<BLANKLINE>"]

0 commit comments

Comments
 (0)