Skip to content

Commit 4fe528a

Browse files
committed
Implement completionItem/resolve
1 parent bd1d0a1 commit 4fe528a

File tree

5 files changed

+203
-154
lines changed

5 files changed

+203
-154
lines changed

Diff for: ghcide/src/Development/IDE/GHC/Compat.hs

+20
Original file line numberDiff line numberDiff line change
@@ -22,6 +22,7 @@ module Development.IDE.GHC.Compat(
2222
#else
2323
upNameCache,
2424
#endif
25+
lookupNameCache,
2526
disableWarningsAsErrors,
2627
reLoc,
2728
reLocA,
@@ -444,6 +445,25 @@ hieExportNames = nameListFromAvails . hie_exports
444445
#if MIN_VERSION_ghc(9,3,0)
445446
type NameCacheUpdater = NameCache
446447
#else
448+
449+
lookupNameCache :: Module -> OccName -> NameCache -> (NameCache, Name)
450+
-- Lookup up the (Module,OccName) in the NameCache
451+
-- If you find it, return it; if not, allocate a fresh original name and extend
452+
-- the NameCache.
453+
-- Reason: this may the first occurrence of (say) Foo.bar we have encountered.
454+
-- If we need to explore its value we will load Foo.hi; but meanwhile all we
455+
-- need is a Name for it.
456+
lookupNameCache mod occ name_cache =
457+
case lookupOrigNameCache (nsNames name_cache) mod occ of {
458+
Just name -> (name_cache, name);
459+
Nothing ->
460+
case takeUniqFromSupply (nsUniqs name_cache) of {
461+
(uniq, us) ->
462+
let
463+
name = mkExternalName uniq mod occ noSrcSpan
464+
new_cache = extendNameCache (nsNames name_cache) mod occ name
465+
in (name_cache{ nsUniqs = us, nsNames = new_cache }, name) }}
466+
447467
upNameCache :: IORef NameCache -> (NameCache -> (NameCache, c)) -> IO c
448468
#if MIN_VERSION_ghc(8,8,0)
449469
upNameCache = updNameCache

Diff for: ghcide/src/Development/IDE/Plugin/Completions.hs

+49-8
Original file line numberDiff line numberDiff line change
@@ -10,40 +10,40 @@ module Development.IDE.Plugin.Completions
1010

1111
import Control.Concurrent.Async (concurrently)
1212
import Control.Concurrent.STM.Stats (readTVarIO)
13-
import Control.Monad.Extra
1413
import Control.Monad.IO.Class
15-
import Control.Monad.Trans.Maybe
14+
import Control.Lens ((&), (.~))
1615
import Data.Aeson
1716
import qualified Data.HashMap.Strict as Map
1817
import qualified Data.HashSet as Set
19-
import Data.List (find)
2018
import Data.Maybe
2119
import qualified Data.Text as T
2220
import Development.IDE.Core.PositionMapping
21+
import Development.IDE.Core.Compile
2322
import Development.IDE.Core.RuleTypes
2423
import Development.IDE.Core.Service hiding (Log, LogShake)
2524
import Development.IDE.Core.Shake hiding (Log)
2625
import qualified Development.IDE.Core.Shake as Shake
2726
import Development.IDE.GHC.Compat
28-
import Development.IDE.GHC.Error (rangeToSrcSpan)
2927
import Development.IDE.GHC.Util (printOutputable)
3028
import Development.IDE.Graph
29+
import Development.IDE.Spans.Common
30+
import Development.IDE.Spans.Documentation
3131
import Development.IDE.Plugin.Completions.Logic
3232
import Development.IDE.Plugin.Completions.Types
3333
import Development.IDE.Types.Exports
34-
import Development.IDE.Types.HscEnvEq (HscEnvEq (envPackageExports),
34+
import Development.IDE.Types.HscEnvEq (HscEnvEq (envPackageExports, envVisibleModuleNames),
3535
hscEnv)
3636
import qualified Development.IDE.Types.KnownTargets as KT
3737
import Development.IDE.Types.Location
3838
import Development.IDE.Types.Logger (Pretty (pretty),
3939
Recorder,
4040
WithPriority,
4141
cmapWithPrio)
42-
import GHC.Exts (fromList, toList)
4342
import Ide.Plugin.Config (Config)
4443
import Ide.Types
4544
import qualified Language.LSP.Server as LSP
4645
import Language.LSP.Types
46+
import qualified Language.LSP.Types.Lens as J
4747
import qualified Language.LSP.VFS as VFS
4848
import Numeric.Natural
4949
import Text.Fuzzy.Parallel (Scored (..))
@@ -61,10 +61,12 @@ descriptor :: Recorder (WithPriority Log) -> PluginId -> PluginDescriptor IdeSta
6161
descriptor recorder plId = (defaultPluginDescriptor plId)
6262
{ pluginRules = produceCompletions recorder
6363
, pluginHandlers = mkPluginHandler STextDocumentCompletion getCompletionsLSP
64+
<> mkPluginHandler SCompletionItemResolve resolveCompletion
6465
, pluginConfigDescriptor = defaultConfigDescriptor {configCustomConfig = mkCustomConfig properties}
6566
, pluginPriority = ghcideCompletionsPluginPriority
6667
}
6768

69+
6870
produceCompletions :: Recorder (WithPriority Log) -> Rules ()
6971
produceCompletions recorder = do
7072
define (cmapWithPrio LogShake recorder) $ \LocalCompletions file -> do
@@ -89,8 +91,9 @@ produceCompletions recorder = do
8991
(global, inScope) <- liftIO $ tcRnImportDecls env (dropListFromImportDecl <$> msrImports) `concurrently` tcRnImportDecls env msrImports
9092
case (global, inScope) of
9193
((_, Just globalEnv), (_, Just inScopeEnv)) -> do
94+
visibleMods <- liftIO $ fmap (fromMaybe []) $ envVisibleModuleNames sess
9295
let uri = fromNormalizedUri $ normalizedFilePathToUri file
93-
cdata <- liftIO $ cacheDataProducer uri sess (ms_mod msrModSummary) globalEnv inScopeEnv msrImports
96+
let cdata = cacheDataProducer uri visibleMods (ms_mod msrModSummary) globalEnv inScopeEnv msrImports
9497
return ([], Just cdata)
9598
(_diag, _) ->
9699
return ([], Nothing)
@@ -106,6 +109,44 @@ dropListFromImportDecl iDecl = let
106109
f x = x
107110
in f <$> iDecl
108111

112+
resolveCompletion :: IdeState -> PluginId -> CompletionItem -> LSP.LspM Config (Either ResponseError CompletionItem)
113+
resolveCompletion ide _ comp@CompletionItem{_detail,_documentation,_xdata}
114+
| Just resolveData <- _xdata
115+
, Success (uri, NameDetails mod occ) <- fromJSON resolveData
116+
, Just file <- uriToNormalizedFilePath $ toNormalizedUri uri = do
117+
mdkm <- liftIO $ runAction "Completion resolve" ide $ use GetDocMap file
118+
case mdkm of
119+
Nothing -> pure (Right comp)
120+
Just (DKMap dm km) -> liftIO $ runAction "Completion resolve" ide $ do
121+
let nc = ideNc $ shakeExtras ide
122+
#if MIN_VERSION_ghc(9,3,0)
123+
name <- liftIO $ lookupNameCache nc mod occ
124+
#else
125+
name <- liftIO $ upNameCache nc (lookupNameCache mod occ)
126+
#endif
127+
(ms,_) <- useWithStale_ GetModSummaryWithoutTimestamps file
128+
(sess,_) <- useWithStale_ GhcSessionDeps file
129+
let cur_mod = ms_mod $ msrModSummary ms
130+
doc <- case lookupNameEnv dm name of
131+
Just doc -> pure $ spanDocToMarkdown doc
132+
Nothing -> liftIO $ spanDocToMarkdown <$> getDocumentationTryGhc (hscEnv sess) cur_mod name
133+
typ <- case lookupNameEnv km name of
134+
Just ty -> pure (safeTyThingType ty)
135+
Nothing -> do
136+
(safeTyThingType =<<) <$> liftIO (lookupName (hscEnv sess) cur_mod name)
137+
let det1 = case typ of
138+
Just ty -> Just (":: " <> printOutputable ty <> "\n")
139+
Nothing -> Nothing
140+
doc1 = case _documentation of
141+
Just (CompletionDocMarkup (MarkupContent MkMarkdown old)) ->
142+
CompletionDocMarkup $ MarkupContent MkMarkdown $ T.intercalate sectionSeparator (old:doc)
143+
_ -> CompletionDocMarkup $ MarkupContent MkMarkdown $ T.intercalate sectionSeparator doc
144+
pure (Right $ comp & J.detail .~ (det1 <> _detail)
145+
& J.documentation .~ Just doc1
146+
)
147+
148+
resolveCompletion _ _ comp = pure (Right comp)
149+
109150
-- | Generate code actions.
110151
getCompletionsLSP
111152
:: IdeState
@@ -151,7 +192,7 @@ getCompletionsLSP ide plId
151192
let clientCaps = clientCapabilities $ shakeExtras ide
152193
plugins = idePlugins $ shakeExtras ide
153194
config <- getCompletionsConfig plId
154-
allCompletions <- liftIO $ getCompletions plugins ideOpts cci' parsedMod bindMap pfix' clientCaps config moduleExports
195+
allCompletions <- liftIO $ getCompletions plugins ideOpts cci' parsedMod bindMap pfix' clientCaps config moduleExports uri
155196
pure $ InL (List $ orderedCompletions allCompletions)
156197
_ -> return (InL $ List [])
157198
_ -> return (InL $ List [])

0 commit comments

Comments
 (0)