@@ -36,13 +36,8 @@ import Control.Monad.IO.Class (MonadIO (liftIO))
36
36
import Control.Monad.Trans.Except
37
37
( ExceptT (.. ),
38
38
)
39
- import Data.Aeson
40
- ( FromJSON ,
41
- ToJSON ,
42
- toJSON ,
43
- )
39
+ import Data.Aeson (toJSON )
44
40
import Data.Char (isSpace )
45
- import Data.Either (isRight )
46
41
import qualified Data.HashMap.Strict as HashMap
47
42
import Data.List
48
43
(dropWhileEnd ,
@@ -59,10 +54,10 @@ import qualified Data.Text as T
59
54
import Data.Time (getCurrentTime )
60
55
import Data.Typeable (Typeable )
61
56
import Development.IDE
62
- (realSrcSpanToRange , GetModSummary (.. ),
57
+ ( Action ,
58
+ realSrcSpanToRange , GetModSummary (.. ),
63
59
GetParsedModuleWithComments (.. ),
64
- GhcSession (.. ),
65
- HscEnvEq (envImportPaths ),
60
+ HscEnvEq ,
66
61
IdeState ,
67
62
List (List ),
68
63
NormalizedFilePath ,
@@ -77,9 +72,15 @@ import Development.IDE
77
72
toNormalizedUri ,
78
73
uriToFilePath' ,
79
74
useWithStale_ ,
80
- use_ , prettyPrint
75
+ prettyPrint ,
76
+ use_ , useNoFile_ , uses_ ,
77
+ GhcSessionIO (.. ), GetDependencies (.. ), GetModIface (.. ),
78
+ HiFileResult (hirHomeMod , hirModSummary )
81
79
)
80
+ import Development.IDE.Core.Rules (TransitiveDependencies (transitiveModuleDeps ))
81
+ import Development.IDE.Core.Compile (setupFinderCache , loadModulesHome )
82
82
import Development.IDE.GHC.Compat (AnnotationComment (AnnBlockComment , AnnLineComment ), GenLocated (L ), HscEnv , ParsedModule (.. ), SrcSpan (RealSrcSpan , UnhelpfulSpan ), srcSpanFile , GhcException , setInteractiveDynFlags )
83
+ import Development.IDE.Types.Options
83
84
import DynamicLoading (initializePlugins )
84
85
import FastString (unpackFS )
85
86
import GHC
@@ -109,16 +110,14 @@ import GHC
109
110
load ,
110
111
runDecls ,
111
112
setContext ,
112
- setInteractiveDynFlags ,
113
113
setLogAction ,
114
114
setSessionDynFlags ,
115
115
setTargets ,
116
116
typeKind ,
117
117
)
118
- import GHC.Generics (Generic )
119
- import qualified GHC.LanguageExtensions.Type as LangExt
120
118
import GhcPlugins
121
119
( DynFlags (.. ),
120
+ hsc_dflags ,
122
121
defaultLogActionHPutStrDoc ,
123
122
gopt_set ,
124
123
gopt_unset ,
@@ -147,15 +146,14 @@ import Ide.Plugin.Eval.Code
147
146
testRanges ,
148
147
)
149
148
import Ide.Plugin.Eval.GHC
150
- ( addExtension ,
151
- addImport ,
149
+ ( addImport ,
152
150
addPackages ,
153
151
hasPackage ,
154
152
isExpr ,
155
153
showDynFlags ,
156
154
)
157
155
import Ide.Plugin.Eval.Parse.Comments (commentsToSections )
158
- import Ide.Plugin.Eval.Parse.Option (langOptions , parseSetFlags )
156
+ import Ide.Plugin.Eval.Parse.Option (parseSetFlags )
159
157
import Ide.Plugin.Eval.Types
160
158
import Ide.Plugin.Eval.Util
161
159
( asS ,
@@ -214,7 +212,6 @@ import Outputable
214
212
import System.FilePath (takeFileName )
215
213
import System.IO (hClose )
216
214
import System.IO.Temp (withSystemTempFile )
217
- import Text.Read (readMaybe )
218
215
import Util (OverridingBool (Never ))
219
216
import Development.IDE.Core.PositionMapping (toCurrentRange )
220
217
import qualified Data.DList as DL
@@ -344,14 +341,14 @@ runEvalCmd lsp st EvalParams{..} =
344
341
(Just (textToStringBuffer mdlText, now))
345
342
346
343
-- 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
348
345
env <- getSession
349
346
350
347
-- Install the module pragmas and options
351
348
df <- liftIO $ setupDynFlagsForGHCiLike env $ ms_hspp_opts ms
352
349
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
355
352
df <- return df{importPaths = impPaths}
356
353
357
354
-- Set the modified flags in the session
@@ -640,14 +637,29 @@ prettyWarn Warn{..} =
640
637
prettyPrint (SrcLoc. getLoc warnMsg) <> " : warning:\n "
641
638
<> " " <> SrcLoc. unLoc warnMsg
642
639
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
651
663
652
664
needsQuickCheck :: [(Section , Test )] -> Bool
653
665
needsQuickCheck = any (isProperty . snd )
@@ -670,23 +682,6 @@ errorLines =
670
682
. T. lines
671
683
. T. pack
672
684
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
-
690
685
{- |
691
686
>>> map (pad_ (T.pack "--")) (map T.pack ["2+2",""])
692
687
["--2+2","--<BLANKLINE>"]
0 commit comments