Skip to content

Commit 7dc6e26

Browse files
authored
Completions need not depend on typecheck of the current file (#670)
* Faster completions * optimize withProgressVar We never remove elements from the map so alter is unnecesary * [ghcide-bench] accept ghcide options * Expand completion tests suite * hlints * completions for local foreign decls * Minor improvements for local completions * Restore completion docs in legacy code path * Compatibility with GHC < 8.8 * fix merge issue * address review feedback
1 parent 035019d commit 7dc6e26

File tree

15 files changed

+397
-219
lines changed

15 files changed

+397
-219
lines changed

.hlint.yaml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -95,7 +95,7 @@
9595
- flags:
9696
- default: false
9797
- {name: [-Wno-missing-signatures, -Wno-orphans, -Wno-overlapping-patterns, -Wno-incomplete-patterns, -Wno-missing-fields, -Wno-unused-matches]}
98-
- {name: [-Wno-dodgy-imports], within: Main}
98+
- {name: [-Wno-dodgy-imports], within: [Main, Development.IDE.GHC.Compat]}
9999
# - modules:
100100
# - {name: [Data.Set, Data.HashSet], as: Set} # if you import Data.Set qualified, it must be as 'Set'
101101
# - {name: Control.Arrow, within: []} # Certain modules are banned entirely

bench/hist/Main.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -204,7 +204,7 @@ main = shakeArgs shakeOptions {shakeChange = ChangeModtimeAndDigest} $ do
204204
"--samples=" <> show samples,
205205
"--csv=" <> outcsv,
206206
"--example-package-version=3.0.0.0",
207-
"--rts=-I0.5",
207+
"--ghcide-options= +RTS -I0.5 -RTS",
208208
"--ghcide=" <> ghcide,
209209
"--select",
210210
unescaped (unescapeExperiment (Escaped $ dropExtension exp))

bench/lib/Experiments.hs

Lines changed: 5 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -146,7 +146,7 @@ data Config = Config
146146
shakeProfiling :: !(Maybe FilePath),
147147
outputCSV :: !FilePath,
148148
buildTool :: !CabalStack,
149-
rtsOptions :: ![String],
149+
ghcideOptions :: ![String],
150150
matches :: ![String],
151151
repetitions :: Maybe Natural,
152152
ghcide :: FilePath,
@@ -177,7 +177,7 @@ configP =
177177
<*> optional (strOption (long "shake-profiling" <> metavar "PATH"))
178178
<*> strOption (long "csv" <> metavar "PATH" <> value "results.csv" <> showDefault)
179179
<*> flag Cabal Stack (long "stack" <> help "Use stack (by default cabal is used)")
180-
<*> many (strOption (long "rts" <> help "additional RTS options for ghcide"))
180+
<*> many (strOption (long "ghcide-options" <> help "additional options for ghcide"))
181181
<*> many (strOption (short 's' <> long "select" <> help "select which benchmarks to run"))
182182
<*> optional (option auto (long "samples" <> metavar "NAT" <> help "override sampling count"))
183183
<*> strOption (long "ghcide" <> metavar "PATH" <> help "path to ghcide" <> value "ghcide")
@@ -283,11 +283,10 @@ runBenchmarks allBenchmarks = do
283283
"--cwd",
284284
dir,
285285
"+RTS",
286-
"-S" <> gcStats name
286+
"-S" <> gcStats name,
287+
"-RTS"
287288
]
288-
++ rtsOptions ?config
289-
++ [ "-RTS"
290-
]
289+
++ ghcideOptions ?config
291290
++ concat
292291
[ ["--shake-profiling", path]
293292
| Just path <- [shakeProfiling ?config]

src/Development/IDE/Core/Compile.hs

Lines changed: 35 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -12,6 +12,7 @@ module Development.IDE.Core.Compile
1212
, RunSimplifier(..)
1313
, compileModule
1414
, parseModule
15+
, parseHeader
1516
, typecheckModule
1617
, computePackageDeps
1718
, addRelativeImport
@@ -483,6 +484,39 @@ getModSummaryFromImports fp contents = do
483484
}
484485
return summary
485486

487+
-- | Parse only the module header
488+
parseHeader
489+
:: GhcMonad m
490+
=> DynFlags -- ^ flags to use
491+
-> FilePath -- ^ the filename (for source locations)
492+
-> SB.StringBuffer -- ^ Haskell module source text (full Unicode is supported)
493+
-> ExceptT [FileDiagnostic] m ([FileDiagnostic], Located(HsModule GhcPs))
494+
parseHeader dflags filename contents = do
495+
let loc = mkRealSrcLoc (mkFastString filename) 1 1
496+
case unP Parser.parseHeader (mkPState dflags contents loc) of
497+
#if MIN_GHC_API_VERSION(8,10,0)
498+
PFailed pst ->
499+
throwE $ diagFromErrMsgs "parser" dflags $ getErrorMessages pst dflags
500+
#else
501+
PFailed _ locErr msgErr ->
502+
throwE $ diagFromErrMsg "parser" dflags $ mkPlainErrMsg dflags locErr msgErr
503+
#endif
504+
POk pst rdr_module -> do
505+
let (warns, errs) = getMessages pst dflags
506+
-- Just because we got a `POk`, it doesn't mean there
507+
-- weren't errors! To clarify, the GHC parser
508+
-- distinguishes between fatal and non-fatal
509+
-- errors. Non-fatal errors are the sort that don't
510+
-- prevent parsing from continuing (that is, a parse
511+
-- tree can still be produced despite the error so that
512+
-- further errors/warnings can be collected). Fatal
513+
-- errors are those from which a parse tree just can't
514+
-- be produced.
515+
unless (null errs) $
516+
throwE $ diagFromErrMsgs "parser" dflags errs
517+
518+
let warnings = diagFromErrMsgs "parser" dflags warns
519+
return (warnings, rdr_module)
486520

487521
-- | Given a buffer, flags, and file path, produce a
488522
-- parsed module (or errors) and any parse warnings. Does not run any preprocessors
@@ -521,7 +555,7 @@ parseFileContents customPreprocessor dflags comp_pkgs filename contents = do
521555
-- errors are those from which a parse tree just can't
522556
-- be produced.
523557
unless (null errs) $
524-
throwE $ diagFromErrMsgs "parser" dflags $ snd $ getMessages pst dflags
558+
throwE $ diagFromErrMsgs "parser" dflags errs
525559

526560
-- Ok, we got here. It's safe to continue.
527561
let IdePreprocessedSource preproc_warns errs parsed = customPreprocessor rdr_module

src/Development/IDE/Core/Rules.hs

Lines changed: 1 addition & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -683,9 +683,7 @@ getModSummaryRule = defineEarlyCutoff $ \GetModSummary f -> do
683683
getModSummaryFromImports (fromNormalizedFilePath f) (textToStringBuffer <$> mFileContent)
684684
case modS of
685685
Right ms -> do
686-
-- Clear the contents as no longer needed
687-
let !ms' = ms{ms_hspp_buf=Nothing}
688-
return ( Just (computeFingerprint f dflags ms), ([], Just ms'))
686+
return ( Just (computeFingerprint f dflags ms), ([], Just ms))
689687
Left diags -> return (Nothing, (diags, Nothing))
690688
where
691689
-- Compute a fingerprint from the contents of `ModSummary`,

src/Development/IDE/Core/Shake.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -858,7 +858,7 @@ defineEarlyCutoff op = addBuiltinRule noLint noIdentity $ \(Q (key, file)) (old
858858
-- This functions are deliberately eta-expanded to avoid space leaks.
859859
-- Do not remove the eta-expansion without profiling a session with at
860860
-- least 1000 modifications.
861-
where f shift = modifyVar_ var $ \x -> evaluate $ HMap.alter (\x -> Just $! shift (fromMaybe 0 x)) file x
861+
where f shift = modifyVar_ var $ \x -> evaluate $ HMap.insertWith (\_ x -> shift x) file (shift 0) x
862862

863863

864864

src/Development/IDE/GHC/Compat.hs

Lines changed: 44 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,10 @@
22
-- SPDX-License-Identifier: Apache-2.0
33

44
{-# LANGUAGE CPP #-}
5+
{-# LANGUAGE ConstraintKinds #-}
6+
{-# LANGUAGE FlexibleInstances #-}
57
{-# LANGUAGE PatternSynonyms #-}
8+
{-# OPTIONS -Wno-dodgy-imports #-}
69
#include "ghc-api-version.h"
710

811
-- | Attempt at hiding the GHC version differences we can.
@@ -37,11 +40,15 @@ module Development.IDE.GHC.Compat(
3740
pattern ClassOpSig,
3841
pattern IEThingAll,
3942
pattern IEThingWith,
43+
pattern VarPat,
4044
GHC.ModLocation,
4145
Module.addBootSuffix,
4246
pattern ModLocation,
4347
getConArgs,
4448

49+
HasSrcSpan,
50+
getLoc,
51+
4552
module GHC
4653
) where
4754

@@ -54,7 +61,20 @@ import Packages
5461

5562
import qualified GHC
5663
import GHC hiding (
57-
ClassOpSig, DerivD, ForD, IEThingAll, IEThingWith, InstD, TyClD, ValD, SigD, TypeSig, ModLocation
64+
ClassOpSig,
65+
DerivD,
66+
ForD,
67+
IEThingAll,
68+
IEThingWith,
69+
InstD,
70+
TyClD,
71+
ValD,
72+
SigD,
73+
TypeSig,
74+
VarPat,
75+
ModLocation,
76+
HasSrcSpan,
77+
getLoc
5878
#if MIN_GHC_API_VERSION(8,6,0)
5979
, getConArgs
6080
#endif
@@ -92,7 +112,7 @@ import System.IO.Error
92112
import Binary
93113
import Control.Exception (catch)
94114
import Data.ByteString (ByteString)
95-
import GhcPlugins hiding (ModLocation)
115+
import GhcPlugins (Hsc, srcErrorMessages)
96116
import NameCache
97117
import TcRnTypes
98118
import System.IO
@@ -210,6 +230,15 @@ pattern IEThingAll a <-
210230
GHC.IEThingAll a
211231
#endif
212232

233+
pattern VarPat :: Located (IdP p) -> Pat p
234+
pattern VarPat x <-
235+
#if MIN_GHC_API_VERSION(8,6,0)
236+
GHC.VarPat _ x
237+
#else
238+
GHC.VarPat x
239+
#endif
240+
241+
213242
setHieDir :: FilePath -> DynFlags -> DynFlags
214243
setHieDir _f d =
215244
#if MIN_GHC_API_VERSION(8,8,0)
@@ -304,7 +333,20 @@ getHeaderImports
304333
)
305334
#if MIN_GHC_API_VERSION(8,8,0)
306335
getHeaderImports = Hdr.getImports
336+
337+
type HasSrcSpan = GHC.HasSrcSpan
338+
getLoc :: HasSrcSpan a => a -> SrcSpan
339+
getLoc = GHC.getLoc
340+
307341
#else
342+
343+
class HasSrcSpan a where
344+
getLoc :: a -> SrcSpan
345+
instance HasSrcSpan Name where
346+
getLoc = nameSrcSpan
347+
instance HasSrcSpan (GenLocated SrcSpan a) where
348+
getLoc = GHC.getLoc
349+
308350
getHeaderImports a b c d =
309351
catch (Right <$> Hdr.getImports a b c d)
310352
(return . Left . srcErrorMessages)

src/Development/IDE/GHC/Util.hs

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -17,6 +17,7 @@ module Development.IDE.GHC.Util(
1717
ParseResult(..), runParser,
1818
lookupPackageConfig,
1919
textToStringBuffer,
20+
bytestringToStringBuffer,
2021
stringBufferToByteString,
2122
moduleImportPath,
2223
cgGutsToCoreModule,
@@ -113,6 +114,9 @@ runParser flags str parser = unP parser parseState
113114
stringBufferToByteString :: StringBuffer -> ByteString
114115
stringBufferToByteString StringBuffer{..} = PS buf cur len
115116

117+
bytestringToStringBuffer :: ByteString -> StringBuffer
118+
bytestringToStringBuffer (PS buf cur len) = StringBuffer{..}
119+
116120
-- | Pretty print a GHC value using 'unsafeGlobalDynFlags '.
117121
prettyPrint :: Outputable a => a -> String
118122
prettyPrint = showSDoc unsafeGlobalDynFlags . ppr

src/Development/IDE/Plugin/CodeAction.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -46,7 +46,7 @@ import Data.List.Extra
4646
import qualified Data.Text as T
4747
import Data.Tuple.Extra ((&&&))
4848
import HscTypes
49-
import SrcLoc
49+
import SrcLoc (sortLocated)
5050
import Parser
5151
import Text.Regex.TDFA ((=~), (=~~))
5252
import Text.Regex.TDFA.Text()

src/Development/IDE/Plugin/Completions.hs

Lines changed: 72 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -18,23 +18,48 @@ import Development.IDE.Plugin
1818
import Development.IDE.Core.Service
1919
import Development.IDE.Plugin.Completions.Logic
2020
import Development.IDE.Types.Location
21+
import Development.IDE.Types.Options
22+
import Development.IDE.Core.Compile
2123
import Development.IDE.Core.PositionMapping
2224
import Development.IDE.Core.RuleTypes
2325
import Development.IDE.Core.Shake
26+
import Development.IDE.GHC.Compat (hsmodExports, ParsedModule(..), ModSummary (ms_hspp_buf))
27+
2428
import Development.IDE.GHC.Util
2529
import Development.IDE.LSP.Server
30+
import Control.Monad.Trans.Except (runExceptT)
31+
import HscTypes (HscEnv(hsc_dflags))
32+
import Data.Maybe
33+
import Data.Functor ((<&>))
2634

2735
#if !MIN_GHC_API_VERSION(8,6,0) || defined(GHC_LIB)
28-
import Data.Maybe
2936
import Development.IDE.Import.DependencyInformation
3037
#endif
3138

3239
plugin :: Plugin c
3340
plugin = Plugin produceCompletions setHandlersCompletion
3441

42+
3543
produceCompletions :: Rules ()
36-
produceCompletions =
44+
produceCompletions = do
3745
define $ \ProduceCompletions file -> do
46+
local <- useWithStale LocalCompletions file
47+
nonLocal <- useWithStale NonLocalCompletions file
48+
let extract = fmap fst
49+
return ([], extract local <> extract nonLocal)
50+
define $ \LocalCompletions file -> do
51+
pm <- useWithStale GetParsedModule file
52+
case pm of
53+
Just (pm, _) -> do
54+
let cdata = localCompletionsForParsedModule pm
55+
return ([], Just cdata)
56+
_ -> return ([], Nothing)
57+
define $ \NonLocalCompletions file -> do
58+
-- For non local completions we avoid depending on the parsed module,
59+
-- synthetizing a fake module with an empty body from the buffer
60+
-- in the ModSummary, which preserves all the imports
61+
ms <- fmap fst <$> useWithStale GetModSummary file
62+
sess <- fmap fst <$> useWithStale GhcSessionDeps file
3863

3964
-- When possible, rely on the haddocks embedded in our interface files
4065
-- This creates problems on ghc-lib, see comment on 'getDocumentationTryGhc'
@@ -44,25 +69,61 @@ produceCompletions =
4469
deps <- maybe (TransitiveDependencies [] [] []) fst <$> useWithStale GetDependencies file
4570
parsedDeps <- mapMaybe (fmap fst) <$> usesWithStale GetParsedModule (transitiveModuleDeps deps)
4671
#endif
47-
tm <- fmap fst <$> useWithStale TypeCheck file
48-
packageState <- fmap (hscEnv . fst) <$> useWithStale GhcSession file
49-
case (tm, packageState) of
50-
(Just tm', Just packageState') -> do
51-
cdata <- liftIO $ cacheDataProducer packageState'
52-
(tmrModule tm') parsedDeps
53-
return ([], Just cdata)
54-
_ -> return ([], Nothing)
5572

73+
case (ms, sess) of
74+
(Just ms, Just sess) -> do
75+
-- After parsing the module remove all package imports referring to
76+
-- these packages as we have already dealt with what they map to.
77+
let env = hscEnv sess
78+
buf = fromJust $ ms_hspp_buf ms
79+
f = fromNormalizedFilePath file
80+
dflags = hsc_dflags env
81+
pm <- liftIO $ evalGhcEnv env $ runExceptT $ parseHeader dflags f buf
82+
case pm of
83+
Right (_diags, hsMod) -> do
84+
let hsModNoExports = hsMod <&> \x -> x{hsmodExports = Nothing}
85+
pm = ParsedModule
86+
{ pm_mod_summary = ms
87+
, pm_parsed_source = hsModNoExports
88+
, pm_extra_src_files = [] -- src imports not allowed
89+
, pm_annotations = mempty
90+
}
91+
tm <- liftIO $ typecheckModule (IdeDefer True) env pm
92+
case tm of
93+
(_, Just (_,TcModuleResult{..})) -> do
94+
cdata <- liftIO $ cacheDataProducer env tmrModule parsedDeps
95+
-- Do not return diags from parsing as they would duplicate
96+
-- the diagnostics from typechecking
97+
return ([], Just cdata)
98+
(_diag, _) ->
99+
return ([], Nothing)
100+
Left _diag ->
101+
return ([], Nothing)
102+
_ -> return ([], Nothing)
56103

57104
-- | Produce completions info for a file
58105
type instance RuleResult ProduceCompletions = CachedCompletions
106+
type instance RuleResult LocalCompletions = CachedCompletions
107+
type instance RuleResult NonLocalCompletions = CachedCompletions
59108

60109
data ProduceCompletions = ProduceCompletions
61110
deriving (Eq, Show, Typeable, Generic)
62111
instance Hashable ProduceCompletions
63112
instance NFData ProduceCompletions
64113
instance Binary ProduceCompletions
65114

115+
data LocalCompletions = LocalCompletions
116+
deriving (Eq, Show, Typeable, Generic)
117+
instance Hashable LocalCompletions
118+
instance NFData LocalCompletions
119+
instance Binary LocalCompletions
120+
121+
data NonLocalCompletions = NonLocalCompletions
122+
deriving (Eq, Show, Typeable, Generic)
123+
instance Hashable NonLocalCompletions
124+
instance NFData NonLocalCompletions
125+
instance Binary NonLocalCompletions
126+
66127

67128
-- | Generate code actions.
68129
getCompletionsLSP
@@ -91,6 +152,7 @@ getCompletionsLSP lsp ide
91152
(Just (VFS.PosPrefixInfo _ "" _ _), Just CompletionContext { _triggerCharacter = Just "."})
92153
-> return (Completions $ List [])
93154
(Just pfix', _) -> do
155+
-- TODO pass the real capabilities here (or remove the logic for snippets)
94156
let fakeClientCapabilities = ClientCapabilities Nothing Nothing Nothing Nothing
95157
Completions . List <$> getCompletions ideOpts cci' pm pfix' fakeClientCapabilities (WithSnippets True)
96158
_ -> return (Completions $ List [])

0 commit comments

Comments
 (0)