Skip to content

Commit dc997a9

Browse files
committed
Add "Goto Implementation" LSP handler
Adds the necessary instances for handling the request type `Method_TextDocumentImplementation`. Further, wire up the appropriate handlers for the "gotoImplementation" request.
1 parent fdba4e5 commit dc997a9

File tree

7 files changed

+92
-28
lines changed

7 files changed

+92
-28
lines changed

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

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,7 @@ module Development.IDE.Core.Actions
33
( getAtPoint
44
, getDefinition
55
, getTypeDefinition
6+
, getImplementationDefinition
67
, highlightAtPoint
78
, refsAtPoint
89
, workspaceSymbols
@@ -120,6 +121,15 @@ getTypeDefinition file pos = runMaybeT $ do
120121
pure $ Just (fixedLocation, identifier)
121122
) locationsWithIdentifier
122123

124+
getImplementationDefinition :: NormalizedFilePath -> Position -> IdeAction (Maybe [Location])
125+
getImplementationDefinition file pos = runMaybeT $ do
126+
ide@ShakeExtras{ withHieDb, hiedbWriter } <- ask
127+
opts <- liftIO $ getIdeOptionsIO ide
128+
(hf, mapping) <- useWithStaleFastMT GetHieAst file
129+
!pos' <- MaybeT (pure $ fromCurrentPosition mapping pos)
130+
locs <- AtPoint.gotoImplementation withHieDb (lookupMod hiedbWriter) opts hf pos'
131+
traverse (MaybeT . toCurrentLocation mapping file) locs
132+
123133
highlightAtPoint :: NormalizedFilePath -> Position -> IdeAction (Maybe [DocumentHighlight])
124134
highlightAtPoint file pos = runMaybeT $ do
125135
(HAR _ hf rf _ _,mapping) <- useWithStaleFastMT GetHieAst file

ghcide/src/Development/IDE/LSP/HoverDefinition.hs

Lines changed: 5 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,7 @@ module Development.IDE.LSP.HoverDefinition
1010
, foundHover
1111
, gotoDefinition
1212
, gotoTypeDefinition
13+
, gotoImplementation
1314
, documentHighlight
1415
, references
1516
, wsSymbols
@@ -47,9 +48,11 @@ instance Pretty Log where
4748
gotoDefinition :: Recorder (WithPriority Log) -> IdeState -> TextDocumentPositionParams -> ExceptT PluginError (HandlerM c) (MessageResult Method_TextDocumentDefinition)
4849
hover :: Recorder (WithPriority Log) -> IdeState -> TextDocumentPositionParams -> ExceptT PluginError (HandlerM c) (Hover |? Null)
4950
gotoTypeDefinition :: Recorder (WithPriority Log) -> IdeState -> TextDocumentPositionParams -> ExceptT PluginError (HandlerM c) (MessageResult Method_TextDocumentTypeDefinition)
51+
gotoImplementation :: Recorder (WithPriority Log) -> IdeState -> TextDocumentPositionParams -> ExceptT PluginError (HandlerM c) (MessageResult Method_TextDocumentImplementation)
5052
documentHighlight :: Recorder (WithPriority Log) -> IdeState -> TextDocumentPositionParams -> ExceptT PluginError (HandlerM c) ([DocumentHighlight] |? Null)
51-
gotoDefinition = request "Definition" getDefinition (InR $ InR Null) (InL . Definition. InR . map fst)
52-
gotoTypeDefinition = request "TypeDefinition" getTypeDefinition (InR $ InR Null) (InL . Definition. InR . map fst)
53+
gotoDefinition = request "Definition" getDefinition (InR $ InR Null) (InL . Definition . InR . map fst)
54+
gotoTypeDefinition = request "TypeDefinition" getTypeDefinition (InR $ InR Null) (InL . Definition . InR . map fst)
55+
gotoImplementation = request "Implementation" getImplementationDefinition (InR $ InR Null) (InL . Definition . InR)
5356
hover = request "Hover" getAtPoint (InR Null) foundHover
5457
documentHighlight = request "DocumentHighlight" highlightAtPoint (InR Null) InL
5558

ghcide/src/Development/IDE/Plugin/HLS/GhcIde.hs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -51,6 +51,8 @@ descriptor recorder plId = (defaultPluginDescriptor plId desc)
5151
Hover.gotoDefinition recorder ide TextDocumentPositionParams{..})
5252
<> mkPluginHandler SMethod_TextDocumentTypeDefinition (\ide _ TypeDefinitionParams{..} ->
5353
Hover.gotoTypeDefinition recorder ide TextDocumentPositionParams{..})
54+
<> mkPluginHandler SMethod_TextDocumentImplementation (\ide _ ImplementationParams{..} ->
55+
Hover.gotoImplementation recorder ide TextDocumentPositionParams{..})
5456
<> mkPluginHandler SMethod_TextDocumentDocumentHighlight (\ide _ DocumentHighlightParams{..} ->
5557
Hover.documentHighlight recorder ide TextDocumentPositionParams{..})
5658
<> mkPluginHandler SMethod_TextDocumentReferences (Hover.references recorder)

ghcide/src/Development/IDE/Spans/AtPoint.hs

Lines changed: 44 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,7 @@ module Development.IDE.Spans.AtPoint (
1010
atPoint
1111
, gotoDefinition
1212
, gotoTypeDefinition
13+
, gotoImplementation
1314
, documentHighlight
1415
, pointCommand
1516
, referencesAtPoint
@@ -58,6 +59,8 @@ import qualified Data.Array as A
5859
import Data.Either
5960
import Data.List.Extra (dropEnd1, nubOrd)
6061

62+
63+
import Data.Either.Extra (eitherToMaybe)
6164
import Data.List (isSuffixOf, sortOn)
6265
import Data.Tree
6366
import qualified Data.Tree as T
@@ -214,6 +217,19 @@ gotoDefinition
214217
gotoDefinition withHieDb getHieFile ideOpts imports srcSpans pos
215218
= lift $ locationsAtPoint withHieDb getHieFile ideOpts imports pos srcSpans
216219

220+
-- | Locate the implementation definition of the name at a given position.
221+
-- Goto Implementation for an overloaded function.
222+
gotoImplementation
223+
:: MonadIO m
224+
=> WithHieDb
225+
-> LookupModule m
226+
-> IdeOptions
227+
-> HieAstResult
228+
-> Position
229+
-> MaybeT m [Location]
230+
gotoImplementation withHieDb getHieFile ideOpts srcSpans pos
231+
= lift $ instanceLocationsAtPoint withHieDb getHieFile ideOpts pos srcSpans
232+
217233
-- | Synopsis for the name at a given position.
218234
atPoint
219235
:: IdeOptions
@@ -228,7 +244,7 @@ atPoint IdeOptions{} (HAR _ (hf :: HieASTs a) rf _ (kind :: HieKind hietype)) (D
228244
-- Hover info for values/data
229245
hoverInfo :: HieAST hietype -> IO (Maybe Range, [T.Text])
230246
hoverInfo ast = do
231-
prettyNames <- mapM prettyName filteredNames
247+
prettyNames <- mapM prettyName names
232248
pure (Just range, prettyNames ++ pTypes)
233249
where
234250
pTypes :: [T.Text]
@@ -245,27 +261,20 @@ atPoint IdeOptions{} (HAR _ (hf :: HieASTs a) rf _ (kind :: HieKind hietype)) (D
245261
info :: NodeInfo hietype
246262
info = nodeInfoH kind ast
247263

264+
-- We want evidence variables to be displayed last.
265+
-- Evidence trees contain information of secondary relevance.
248266
names :: [(Identifier, IdentifierDetails hietype)]
249267
names = sortOn (any isEvidenceUse . identInfo . snd) $ M.assocs $ nodeIdentifiers info
250268

251-
-- Check for evidence bindings
252-
isInternal :: (Identifier, IdentifierDetails a) -> Bool
253-
isInternal (Right _, dets) =
254-
any isEvidenceContext $ identInfo dets
255-
isInternal (Left _, _) = False
256-
257-
filteredNames :: [(Identifier, IdentifierDetails hietype)]
258-
filteredNames = filter (not . isInternal) names
259-
260269
prettyName :: (Either ModuleName Name, IdentifierDetails hietype) -> IO T.Text
261270
prettyName (Right n, dets)
262-
| any isEvidenceUse (identInfo dets) =
263-
pure $ maybe "" (printOutputable . renderEvidenceTree) (getEvidenceTree rf n) <> "\n"
271+
-- We want to print evidence variable using a readable tree structure.
272+
| any isEvidenceUse (identInfo dets) = pure $ maybe "" (printOutputable . renderEvidenceTree) (getEvidenceTree rf n) <> "\n"
264273
| otherwise = pure $ T.unlines $
265274
wrapHaskell (printOutputable n <> maybe "" (" :: " <>) ((prettyType <$> identType dets) <|> maybeKind))
266275
: maybeToList (pretty (definedAt n) (prettyPackageName n))
267276
++ catMaybes [ T.unlines . spanDocToMarkdown <$> lookupNameEnv dm n
268-
]
277+
]
269278
where maybeKind = fmap printOutputable $ safeTyThingType =<< lookupNameEnv km n
270279
pretty Nothing Nothing = Nothing
271280
pretty (Just define) Nothing = Just $ define <> "\n"
@@ -299,7 +308,7 @@ atPoint IdeOptions{} (HAR _ (hf :: HieASTs a) rf _ (kind :: HieKind hietype)) (D
299308
version = T.pack $ showVersion (unitPackageVersion conf)
300309
pure $ pkgName <> "-" <> version
301310

302-
-- Type info for the current node, it may contains several symbols
311+
-- Type info for the current node, it may contain several symbols
303312
-- for one range, like wildcard
304313
types :: [hietype]
305314
types = nodeType info
@@ -308,10 +317,7 @@ atPoint IdeOptions{} (HAR _ (hf :: HieASTs a) rf _ (kind :: HieKind hietype)) (D
308317
prettyTypes = map (("_ :: "<>) . prettyType) types
309318

310319
prettyType :: hietype -> T.Text
311-
prettyType t = case kind of
312-
HieFresh -> printOutputable t
313-
HieFromDisk full_file -> printOutputable $ hieTypeToIface $ recoverFullType t (hie_types full_file)
314-
-- prettyType = printOutputable . expandType
320+
prettyType = printOutputable . expandType
315321

316322
expandType :: a -> SDoc
317323
expandType t = case kind of
@@ -352,7 +358,7 @@ atPoint IdeOptions{} (HAR _ (hf :: HieASTs a) rf _ (kind :: HieKind hietype)) (D
352358
printDets ospn (Just (src,_,mspn)) = pprSrc
353359
$$ text "at" <+> ppr spn
354360
where
355-
-- Use the bind span if we have one, else use the occurence span
361+
-- Use the bind span if we have one, else use the occurrence span
356362
spn = fromMaybe ospn mspn
357363
pprSrc = case src of
358364
-- Users don't know what HsWrappers are
@@ -419,15 +425,31 @@ locationsAtPoint
419425
-> m [(Location, Identifier)]
420426
locationsAtPoint withHieDb lookupModule _ideOptions imports pos (HAR _ ast _rm _ _) =
421427
let ns = concat $ pointCommand ast pos (M.keys . getNodeIds)
422-
evTrees = mapMaybe (either (const Nothing) $ getEvidenceTree _rm) ns
423-
evNs = concatMap (map (Right . evidenceVar) . T.flatten) evTrees
424428
zeroPos = Position 0 0
425429
zeroRange = Range zeroPos zeroPos
426430
modToLocation m = fmap (\fs -> pure (Location (fromNormalizedUri $ filePathToUri' fs) zeroRange)) $ M.lookup m imports
427431
in fmap (nubOrd . concat) $ mapMaybeM
428432
(either (\m -> pure ((fmap $ fmap (,Left m)) (modToLocation m)))
429433
(\n -> fmap (fmap $ fmap (,Right n)) (nameToLocation withHieDb lookupModule n)))
430-
(ns ++ evNs)
434+
ns
435+
436+
-- | Find 'Location's of a implementation definition at a specific point.
437+
instanceLocationsAtPoint
438+
:: forall m
439+
. MonadIO m
440+
=> WithHieDb
441+
-> LookupModule m
442+
-> IdeOptions
443+
-> Position
444+
-> HieAstResult
445+
-> m [Location]
446+
instanceLocationsAtPoint withHieDb lookupModule _ideOptions pos (HAR _ ast _rm _ _) =
447+
let ns = concat $ pointCommand ast pos (M.keys . getNodeIds)
448+
evTrees = mapMaybe (eitherToMaybe >=> getEvidenceTree _rm) ns
449+
evNs = concatMap (map (evidenceVar) . T.flatten) evTrees
450+
in fmap (nubOrd . concat) $ mapMaybeM
451+
(nameToLocation withHieDb lookupModule)
452+
evNs
431453

432454
-- | Given a 'Name' attempt to find the location where it is defined.
433455
nameToLocation :: MonadIO m => WithHieDb -> LookupModule m -> Name -> m (Maybe [Location])

ghcide/test/exe/FindDefinitionAndHoverTests.hs

Lines changed: 22 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -13,6 +13,7 @@ import Language.LSP.Test
1313
import System.Info.Extra (isWindows)
1414

1515
import Config
16+
import Control.Category ((>>>))
1617
import Control.Lens ((^.))
1718
import Development.IDE.Test (expectDiagnostics,
1819
standardizeQuotes)
@@ -53,7 +54,27 @@ tests = let
5354
_ -> liftIO $ assertFailure $ "test not expecting this kind of hover info" <> show hover
5455

5556
extractLineColFromHoverMsg :: T.Text -> [T.Text]
56-
extractLineColFromHoverMsg = T.splitOn ":" . head . T.splitOn "*" . last . T.splitOn (sourceFileName <> ":")
57+
extractLineColFromHoverMsg =
58+
-- Hover messages contain multiple lines, and we are looking for the definition
59+
-- site
60+
T.lines
61+
-- The line we are looking for looks like: "*Defined at /tmp/GotoHover.hs:22:3*"
62+
-- So filter by the start of the line
63+
>>> mapMaybe (T.stripPrefix "*Defined at")
64+
-- There can be multiple definitions per hover message!
65+
-- See the test "field in record definition" for example.
66+
-- The tests check against the last line that contains the above line.
67+
>>> last
68+
-- [" /tmp/", "22:3*"]
69+
>>> T.splitOn (sourceFileName <> ":")
70+
-- "22:3*"
71+
>>> last
72+
-- ["22:3", ""]
73+
>>> T.splitOn "*"
74+
-- "22:3"
75+
>>> head
76+
-- ["22", "3"]
77+
>>> T.splitOn ":"
5778

5879
checkHoverRange :: Range -> Maybe Range -> T.Text -> Session ()
5980
checkHoverRange expectedRange rangeInHover msg =

ghcide/test/exe/InitializeResponseTests.hs

Lines changed: 1 addition & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -33,9 +33,7 @@ tests = withResource acquire release tests where
3333
, chk "NO signature help" _signatureHelpProvider Nothing
3434
, chk " goto definition" _definitionProvider (Just $ InR (DefinitionOptions (Just False)))
3535
, chk " goto type definition" _typeDefinitionProvider (Just $ InR (InL (TypeDefinitionOptions (Just False))))
36-
-- BUG in lsp-test, this test fails, just change the accepted response
37-
-- for now
38-
, chk "NO goto implementation" _implementationProvider Nothing
36+
, chk " goto implementation" _implementationProvider (Just $ InR (InL (ImplementationOptions (Just False))))
3937
, chk " find references" _referencesProvider (Just $ InR (ReferenceOptions (Just False)))
4038
, chk " doc highlight" _documentHighlightProvider (Just $ InR (DocumentHighlightOptions (Just False)))
4139
, chk " doc symbol" _documentSymbolProvider (Just $ InR (DocumentSymbolOptions (Just False) Nothing))

hls-plugin-api/src/Ide/Types.hs

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -503,6 +503,9 @@ instance PluginMethod Request Method_TextDocumentDefinition where
503503
instance PluginMethod Request Method_TextDocumentTypeDefinition where
504504
handlesRequest _ msgParams pluginDesc _ = pluginSupportsFileType msgParams pluginDesc
505505

506+
instance PluginMethod Request Method_TextDocumentImplementation where
507+
handlesRequest _ msgParams pluginDesc _ = pluginSupportsFileType msgParams pluginDesc
508+
506509
instance PluginMethod Request Method_TextDocumentDocumentHighlight where
507510
handlesRequest _ msgParams pluginDesc _ = pluginSupportsFileType msgParams pluginDesc
508511

@@ -696,6 +699,11 @@ instance PluginRequestMethod Method_TextDocumentTypeDefinition where
696699
| Just (Just True) <- caps ^? (L.textDocument . _Just . L.typeDefinition . _Just . L.linkSupport) = foldl' mergeDefinitions x xs
697700
| otherwise = downgradeLinks $ foldl' mergeDefinitions x xs
698701

702+
instance PluginRequestMethod Method_TextDocumentImplementation where
703+
combineResponses _ _ caps _ (x :| xs)
704+
| Just (Just True) <- caps ^? (L.textDocument . _Just . L.implementation . _Just . L.linkSupport) = foldl' mergeDefinitions x xs
705+
| otherwise = downgradeLinks $ foldl' mergeDefinitions x xs
706+
699707
instance PluginRequestMethod Method_TextDocumentDocumentHighlight where
700708

701709
instance PluginRequestMethod Method_TextDocumentReferences where

0 commit comments

Comments
 (0)