Skip to content

Commit 70a2a1a

Browse files
committed
Improve documentation for Evidence tree rendering
Also, add extensive note about skipping 'EvLetBinding' evidence nodes.
1 parent b773ab2 commit 70a2a1a

File tree

1 file changed

+45
-9
lines changed

1 file changed

+45
-9
lines changed

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

Lines changed: 45 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -270,12 +270,26 @@ atPoint IdeOptions{} (HAR _ (hf :: HieASTs a) rf _ (kind :: HieKind hietype)) (D
270270
prettyName :: (Either ModuleName Name, IdentifierDetails hietype) -> IO T.Text
271271
prettyName (Right n, dets)
272272
-- We want to print evidence variable using a readable tree structure.
273-
| any isEvidenceUse (identInfo dets) = pure $ maybe "" (printOutputable . renderEvidenceTree) (getEvidenceTree rf n) <> "\n"
274-
| otherwise = pure $ T.unlines $
275-
wrapHaskell (printOutputable n <> maybe "" (" :: " <>) ((prettyType <$> identType dets) <|> maybeKind))
276-
: maybeToList (pretty (definedAt n) (prettyPackageName n))
277-
++ catMaybes [ T.unlines . spanDocToMarkdown <$> lookupNameEnv dm n
278-
]
273+
-- Evidence variables contain information why a particular instance or
274+
-- type equality was chosen, paired with location information.
275+
| any isEvidenceUse (identInfo dets) =
276+
let
277+
-- The evidence tree may not be present for some reason, e.g., the 'Name' is not
278+
-- present in the tree.
279+
-- Thus, we need to handle it here, but in practice, this should never be 'Nothing'.
280+
evidenceTree = maybe "" (printOutputable . renderEvidenceTree) (getEvidenceTree rf n)
281+
in
282+
pure $ evidenceTree <> "\n"
283+
-- Identifier details that are not evidence variables are used to display type information and
284+
-- documentation of that name.
285+
| otherwise =
286+
let
287+
typeSig = wrapHaskell (printOutputable n <> maybe "" (" :: " <>) ((prettyType <$> identType dets) <|> maybeKind))
288+
definitionLoc = maybeToList (pretty (definedAt n) (prettyPackageName n))
289+
docs = maybeToList (T.unlines . spanDocToMarkdown <$> lookupNameEnv dm n)
290+
in
291+
pure $ T.unlines $
292+
[typeSig] ++ definitionLoc ++ docs
279293
where maybeKind = fmap printOutputable $ safeTyThingType =<< lookupNameEnv km n
280294
pretty Nothing Nothing = Nothing
281295
pretty (Just define) Nothing = Just $ define <> "\n"
@@ -338,6 +352,28 @@ atPoint IdeOptions{} (HAR _ (hf :: HieASTs a) rf _ (kind :: HieKind hietype)) (D
338352
renderEvidenceTree :: Tree (EvidenceInfo a) -> SDoc
339353
-- However, if the root constraint is simply a<n indirection (via let) to a single other constraint,
340354
-- we can still skip rendering it
355+
-- A 'let' indirection is conceptually every evidence that is acquired in a 'Let' statement.
356+
-- As a very simple example, take:
357+
--
358+
-- @
359+
-- foo = show 2.0
360+
-- @
361+
--
362+
-- The evidence at 'show' is acquired in a 'Let' (i.e., the definition of 'foo').
363+
-- If we render the evidence tree, it will contain an extra indirection node 'EvLetBind'.
364+
-- Rendering this single indirection will introduce a list which adds virtually no benefit.
365+
-- Compare the output with skipping and then without:
366+
--
367+
-- @
368+
-- Evidence of constraint Show Double bound by type signature or pattern at ...
369+
-- @
370+
--
371+
-- more verbose:
372+
--
373+
-- @
374+
-- Evidence of constraint Show Double constructed using:
375+
-- - Show Double using external instance defined at ...
376+
-- @
341377
renderEvidenceTree (T.Node (EvidenceInfo{evidenceDetails=Just (EvLetBind _,_,_)}) [x])
342378
= renderEvidenceTree x
343379
renderEvidenceTree (T.Node (EvidenceInfo{evidenceDetails=Just (EvLetBind _,_,_), ..}) xs)
@@ -352,15 +388,15 @@ atPoint IdeOptions{} (HAR _ (hf :: HieASTs a) rf _ (kind :: HieKind hietype)) (D
352388
= vcat (map renderEvidenceTree' xs)
353389
renderEvidenceTree' (T.Node (EvidenceInfo{..}) _)
354390
= hang (text "- `" O.<> expandType evidenceType O.<> "`") 2 $
355-
vcat $
356-
printDets evidenceSpan evidenceDetails : map (text . T.unpack) (maybeToList $ definedAt evidenceVar)
391+
vcat $
392+
printDets evidenceSpan evidenceDetails : map (text . T.unpack) (maybeToList $ definedAt evidenceVar)
357393

358394
printDets :: RealSrcSpan -> Maybe (EvVarSource, Scope, Maybe Span) -> SDoc
359395
printDets _ Nothing = text "using an external instance"
360396
printDets ospn (Just (src,_,mspn)) = pprSrc
361397
$$ text "at" <+> text (T.unpack $ srcSpanToMdLink location)
362398
where
363-
location = realSrcSpanToLocation $ traceShowId spn
399+
location = realSrcSpanToLocation spn
364400
-- Use the bind span if we have one, else use the occurrence span
365401
spn = fromMaybe ospn mspn
366402
pprSrc = case src of

0 commit comments

Comments
 (0)