Skip to content

Commit 230a9c9

Browse files
committed
Jump to instance definition and explain typeclass evidence
1 parent f143cf1 commit 230a9c9

File tree

2 files changed

+103
-14
lines changed

2 files changed

+103
-14
lines changed

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

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -86,7 +86,7 @@ getDefinition :: NormalizedFilePath -> Position -> IdeAction (Maybe [Location])
8686
getDefinition file pos = runMaybeT $ do
8787
ide@ShakeExtras{ withHieDb, hiedbWriter } <- ask
8888
opts <- liftIO $ getIdeOptionsIO ide
89-
(HAR _ hf _ _ _, mapping) <- useE GetHieAst file
89+
(hf, mapping) <- useE GetHieAst file
9090
(ImportMap imports, _) <- useE GetImportMap file
9191
!pos' <- MaybeT (pure $ fromCurrentPosition mapping pos)
9292
toCurrentLocations mapping <$> AtPoint.gotoDefinition withHieDb (lookupMod hiedbWriter) opts imports hf pos'

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

Lines changed: 102 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -49,14 +49,22 @@ import qualified Data.Text as T
4949

5050
import qualified Data.Array as A
5151
import Data.Either
52-
import Data.List (isSuffixOf)
5352
import Data.List.Extra (dropEnd1, nubOrd)
5453

5554
import Data.Version (showVersion)
5655
import Development.IDE.Types.Shake (WithHieDb)
5756
import HieDb hiding (pointCommand)
5857
import System.Directory (doesFileExist)
5958

59+
#if MIN_VERSION_ghc(9,0,1)
60+
import qualified Outputable as O
61+
import Data.Tree
62+
import qualified Data.Tree as T
63+
import Data.List (isSuffixOf, sortOn)
64+
#else
65+
import Data.List (isSuffixOf)
66+
#endif
67+
6068
-- | Gives a Uri for the module, given the .hie file location and the the module info
6169
-- The Bool denotes if it is a boot module
6270
type LookupModule m = FilePath -> ModuleName -> Unit -> Bool -> MaybeT m Uri
@@ -197,7 +205,7 @@ gotoDefinition
197205
-> LookupModule m
198206
-> IdeOptions
199207
-> M.Map ModuleName NormalizedFilePath
200-
-> HieASTs a
208+
-> HieAstResult
201209
-> Position
202210
-> MaybeT m [Location]
203211
gotoDefinition withHieDb getHieFile ideOpts imports srcSpans pos
@@ -211,7 +219,7 @@ atPoint
211219
-> HscEnv
212220
-> Position
213221
-> Maybe (Maybe Range, [T.Text])
214-
atPoint IdeOptions{} (HAR _ hf _ _ kind) (DKMap dm km) env pos = listToMaybe $ pointCommand hf pos hoverInfo
222+
atPoint IdeOptions{} (HAR _ (hf :: HieASTs a) _rf _ kind) (DKMap dm km) env pos = listToMaybe $ pointCommand hf pos hoverInfo
215223
where
216224
-- Hover info for values/data
217225
hoverInfo ast = (Just range, prettyNames ++ pTypes)
@@ -224,12 +232,21 @@ atPoint IdeOptions{} (HAR _ hf _ _ kind) (DKMap dm km) env pos = listToMaybe $ p
224232

225233
wrapHaskell x = "\n```haskell\n"<>x<>"\n```\n"
226234
info = nodeInfoH kind ast
227-
names = M.assocs $ nodeIdentifiers info
235+
names =
236+
#if MIN_VERSION_ghc(9,0,1)
237+
sortOn (any isEvidenceUse . identInfo . snd) $
238+
#endif
239+
M.assocs $ nodeIdentifiers info
228240
types = nodeType info
229241

230242
prettyNames :: [T.Text]
231243
prettyNames = map prettyName names
232-
prettyName (Right n, dets) = T.unlines $
244+
prettyName (Right n, dets)
245+
#if MIN_VERSION_ghc(9,0,1)
246+
| any isEvidenceUse (identInfo dets) = maybe "" (printOutputable . renderEvidenceTree) (getEvidenceTree _rf n) <> "\n"
247+
| otherwise
248+
#endif
249+
= T.unlines $
233250
wrapHaskell (printOutputable n <> maybe "" (" :: " <>) ((prettyType <$> identType dets) <|> maybeKind))
234251
: maybeToList (pretty (definedAt n) (prettyPackageName n))
235252
++ catMaybes [ T.unlines . spanDocToMarkdown <$> lookupNameEnv dm n
@@ -250,9 +267,12 @@ atPoint IdeOptions{} (HAR _ hf _ _ kind) (DKMap dm km) env pos = listToMaybe $ p
250267
pure $ "*(" <> pkgName <> "-" <> version <> ")*"
251268

252269
prettyTypes = map (("_ :: "<>) . prettyType) types
253-
prettyType t = case kind of
254-
HieFresh -> printOutputable t
255-
HieFromDisk full_file -> printOutputable $ hieTypeToIface $ recoverFullType t (hie_types full_file)
270+
prettyType = printOutputable . expandType
271+
272+
expandType :: a -> SDoc
273+
expandType t = case kind of
274+
HieFresh -> ppr t
275+
HieFromDisk full_file -> ppr $ hieTypeToIface $ recoverFullType t (hie_types full_file)
256276

257277
definedAt name =
258278
-- do not show "at <no location info>" and similar messages
@@ -261,6 +281,43 @@ atPoint IdeOptions{} (HAR _ hf _ _ kind) (DKMap dm km) env pos = listToMaybe $ p
261281
UnhelpfulLoc {} | isInternalName name || isSystemName name -> Nothing
262282
_ -> Just $ "*Defined " <> printOutputable (pprNameDefnLoc name) <> "*"
263283

284+
#if MIN_VERSION_ghc(9,0,1)
285+
-- We want to render the root constraint even if it is a let,
286+
-- but we don't want to render any subsequent lets
287+
renderEvidenceTree :: Tree (EvidenceInfo a) -> SDoc
288+
-- However, if the root constraint is simply an indirection (via let) to a single other constraint,
289+
-- we can still skip rendering it
290+
renderEvidenceTree (T.Node (EvidenceInfo{evidenceDetails=Just (EvLetBind _,_,_)}) [x])
291+
= renderEvidenceTree x
292+
renderEvidenceTree (T.Node (EvidenceInfo{evidenceDetails=Just (EvLetBind _,_,_), ..}) xs)
293+
= hang (text "- Evidence of constraint `" O.<> expandType evidenceType O.<> "`") 2 $
294+
vcat $ text "depending on:" : map renderEvidenceTree' xs
295+
renderEvidenceTree x = renderEvidenceTree' x
296+
297+
-- renderEvidenceTree' skips let bound evidence variables and prints the children directly
298+
renderEvidenceTree' (T.Node (EvidenceInfo{evidenceDetails=Just (EvLetBind _,_,_)}) xs)
299+
= vcat (map renderEvidenceTree' xs)
300+
renderEvidenceTree' (T.Node (EvidenceInfo{..}) xs)
301+
= hang (text "- Evidence of constraint `" O.<> expandType evidenceType O.<> "`") 2 $
302+
vcat $ map (text . T.unpack) (definedAt evidenceVar)
303+
++ [printDets evidenceSpan evidenceDetails (null xs)]
304+
++ map renderEvidenceTree' xs
305+
306+
printDets :: RealSrcSpan -> Maybe (EvVarSource, Scope, Maybe Span) -> Bool -> SDoc
307+
printDets _ Nothing True = text ""
308+
printDets _ Nothing False = text "constructed using:"
309+
printDets ospn (Just (src,_,mspn)) _ = pprSrc
310+
$$ text "at" <+> ppr spn
311+
where
312+
-- Use the bind span if we have one, else use the occurence span
313+
spn = fromMaybe ospn mspn
314+
pprSrc = case src of
315+
-- Users don't know what HsWrappers are
316+
EvWrapperBind -> "bound by type signature or pattern"
317+
_ -> ppr src
318+
#endif
319+
320+
264321
typeLocationsAtPoint
265322
:: forall m
266323
. MonadIO m
@@ -276,7 +333,7 @@ typeLocationsAtPoint withHieDb lookupModule _ideOptions pos (HAR _ ast _ _ hieKi
276333
let arr = hie_types hf
277334
ts = concat $ pointCommand ast pos getts
278335
unfold = map (arr A.!)
279-
getts x = nodeType ni ++ (mapMaybe identType $ M.elems $ nodeIdentifiers ni)
336+
getts x = nodeType ni ++ mapMaybe identType (M.elems $ nodeIdentifiers ni)
280337
where ni = nodeInfo' x
281338
getTypes ts = flip concatMap (unfold ts) $ \case
282339
HTyVarTy n -> [n]
@@ -295,12 +352,24 @@ typeLocationsAtPoint withHieDb lookupModule _ideOptions pos (HAR _ ast _ _ hieKi
295352
HQualTy a b -> getTypes [a,b]
296353
HCastTy a -> getTypes [a]
297354
_ -> []
355+
<<<<<<< HEAD
298356
in fmap nubOrd $ concatMapM (fmap (fromMaybe []) . nameToLocation withHieDb lookupModule) (getTypes ts)
357+
||||||| parent of dc807c4a (Jump to instance definition and explain typeclass evidence)
358+
in fmap nubOrd $ concatMapM (fmap (fromMaybe []) . nameToLocation hiedb lookupModule) (getTypes ts)
359+
=======
360+
in nubOrd <$> concatMapM (fmap (fromMaybe []) . nameToLocation hiedb lookupModule) (getTypes ts)
361+
>>>>>>> dc807c4a (Jump to instance definition and explain typeclass evidence)
299362
HieFresh ->
300363
let ts = concat $ pointCommand ast pos getts
301-
getts x = nodeType ni ++ (mapMaybe identType $ M.elems $ nodeIdentifiers ni)
364+
getts x = nodeType ni ++ mapMaybe identType (M.elems $ nodeIdentifiers ni)
302365
where ni = nodeInfo x
366+
<<<<<<< HEAD
303367
in fmap nubOrd $ concatMapM (fmap (fromMaybe []) . nameToLocation withHieDb lookupModule) (getTypes ts)
368+
||||||| parent of dc807c4a (Jump to instance definition and explain typeclass evidence)
369+
in fmap nubOrd $ concatMapM (fmap (fromMaybe []) . nameToLocation hiedb lookupModule) (getTypes ts)
370+
=======
371+
in nubOrd <$> concatMapM (fmap (fromMaybe []) . nameToLocation hiedb lookupModule) (getTypes ts)
372+
>>>>>>> dc807c4a (Jump to instance definition and explain typeclass evidence)
304373

305374
namesInType :: Type -> [Name]
306375
namesInType (TyVarTy n) = [varName n]
@@ -313,24 +382,44 @@ namesInType (LitTy _) = []
313382
namesInType _ = []
314383

315384
getTypes :: [Type] -> [Name]
316-
getTypes ts = concatMap namesInType ts
385+
getTypes = concatMap namesInType
317386

318387
locationsAtPoint
319-
:: forall m a
388+
:: forall m
320389
. MonadIO m
321390
=> WithHieDb
322391
-> LookupModule m
323392
-> IdeOptions
324393
-> M.Map ModuleName NormalizedFilePath
325394
-> Position
326-
-> HieASTs a
395+
-> HieAstResult
327396
-> m [Location]
397+
<<<<<<< HEAD
328398
locationsAtPoint withHieDb lookupModule _ideOptions imports pos ast =
399+
||||||| parent of dc807c4a (Jump to instance definition and explain typeclass evidence)
400+
locationsAtPoint hiedb lookupModule _ideOptions imports pos ast =
401+
=======
402+
locationsAtPoint hiedb lookupModule _ideOptions imports pos (HAR _ ast _rm _ _) =
403+
>>>>>>> dc807c4a (Jump to instance definition and explain typeclass evidence)
329404
let ns = concat $ pointCommand ast pos (M.keys . getNodeIds)
405+
#if MIN_VERSION_ghc(9,0,1)
406+
evTrees = mapMaybe (either (const Nothing) $ getEvidenceTree _rm) ns
407+
evNs = concatMap (map (Right . evidenceVar) . T.flatten) evTrees
408+
#else
409+
evNs = []
410+
#endif
330411
zeroPos = Position 0 0
331412
zeroRange = Range zeroPos zeroPos
413+
<<<<<<< HEAD
332414
modToLocation m = fmap (\fs -> pure $ Location (fromNormalizedUri $ filePathToUri' fs) zeroRange) $ M.lookup m imports
333415
in fmap (nubOrd . concat) $ mapMaybeM (either (pure . modToLocation) $ nameToLocation withHieDb lookupModule) ns
416+
||||||| parent of dc807c4a (Jump to instance definition and explain typeclass evidence)
417+
modToLocation m = fmap (\fs -> pure $ Location (fromNormalizedUri $ filePathToUri' fs) zeroRange) $ M.lookup m imports
418+
in fmap (nubOrd . concat) $ mapMaybeM (either (pure . modToLocation) $ nameToLocation hiedb lookupModule) ns
419+
=======
420+
modToLocation m = (\fs -> pure $ Location (fromNormalizedUri $ filePathToUri' fs) zeroRange) <$> M.lookup m imports
421+
in nubOrd . concat <$> mapMaybeM (either (pure . modToLocation) $ nameToLocation hiedb lookupModule) (ns ++ evNs)
422+
>>>>>>> dc807c4a (Jump to instance definition and explain typeclass evidence)
334423

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

0 commit comments

Comments
 (0)