@@ -269,12 +269,26 @@ atPoint IdeOptions{} (HAR _ (hf :: HieASTs a) rf _ (kind :: HieKind hietype)) (D
269
269
prettyName :: (Either ModuleName Name , IdentifierDetails hietype ) -> IO T. Text
270
270
prettyName (Right n, dets)
271
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 "
273
- | otherwise = pure $ T. unlines $
274
- wrapHaskell (printOutputable n <> maybe " " (" :: " <> ) ((prettyType <$> identType dets) <|> maybeKind))
275
- : maybeToList (pretty (definedAt n) (prettyPackageName n))
276
- ++ catMaybes [ T. unlines . spanDocToMarkdown <$> lookupNameEnv dm n
277
- ]
272
+ -- Evidence variables contain information why a particular instance or
273
+ -- type equality was chosen, paired with location information.
274
+ | any isEvidenceUse (identInfo dets) =
275
+ let
276
+ -- The evidence tree may not be present for some reason, e.g., the 'Name' is not
277
+ -- present in the tree.
278
+ -- Thus, we need to handle it here, but in practice, this should never be 'Nothing'.
279
+ evidenceTree = maybe " " (printOutputable . renderEvidenceTree) (getEvidenceTree rf n)
280
+ in
281
+ pure $ evidenceTree <> " \n "
282
+ -- Identifier details that are not evidence variables are used to display type information and
283
+ -- documentation of that name.
284
+ | otherwise =
285
+ let
286
+ typeSig = wrapHaskell (printOutputable n <> maybe " " (" :: " <> ) ((prettyType <$> identType dets) <|> maybeKind))
287
+ definitionLoc = maybeToList (pretty (definedAt n) (prettyPackageName n))
288
+ docs = maybeToList (T. unlines . spanDocToMarkdown <$> lookupNameEnv dm n)
289
+ in
290
+ pure $ T. unlines $
291
+ [typeSig] ++ definitionLoc ++ docs
278
292
where maybeKind = fmap printOutputable $ safeTyThingType =<< lookupNameEnv km n
279
293
pretty Nothing Nothing = Nothing
280
294
pretty (Just define) Nothing = Just $ define <> " \n "
@@ -337,6 +351,28 @@ atPoint IdeOptions{} (HAR _ (hf :: HieASTs a) rf _ (kind :: HieKind hietype)) (D
337
351
renderEvidenceTree :: Tree (EvidenceInfo a ) -> SDoc
338
352
-- However, if the root constraint is simply a<n indirection (via let) to a single other constraint,
339
353
-- we can still skip rendering it
354
+ -- A 'let' indirection is conceptually every evidence that is acquired in a 'Let' statement.
355
+ -- As a very simple example, take:
356
+ --
357
+ -- @
358
+ -- foo = show 2.0
359
+ -- @
360
+ --
361
+ -- The evidence at 'show' is acquired in a 'Let' (i.e., the definition of 'foo').
362
+ -- If we render the evidence tree, it will contain an extra indirection node 'EvLetBind'.
363
+ -- Rendering this single indirection will introduce a list which adds virtually no benefit.
364
+ -- Compare the output with skipping and then without:
365
+ --
366
+ -- @
367
+ -- Evidence of constraint Show Double bound by type signature or pattern at ...
368
+ -- @
369
+ --
370
+ -- more verbose:
371
+ --
372
+ -- @
373
+ -- Evidence of constraint Show Double constructed using:
374
+ -- - Show Double using external instance defined at ...
375
+ -- @
340
376
renderEvidenceTree (T. Node (EvidenceInfo {evidenceDetails= Just (EvLetBind _,_,_)}) [x])
341
377
= renderEvidenceTree x
342
378
renderEvidenceTree (T. Node (EvidenceInfo {evidenceDetails= Just (EvLetBind _,_,_), .. }) xs)
@@ -351,15 +387,15 @@ atPoint IdeOptions{} (HAR _ (hf :: HieASTs a) rf _ (kind :: HieKind hietype)) (D
351
387
= vcat (map renderEvidenceTree' xs)
352
388
renderEvidenceTree' (T. Node (EvidenceInfo {.. }) _)
353
389
= hang (text " - `" O. <> expandType evidenceType O. <> " `" ) 2 $
354
- vcat $
355
- printDets evidenceSpan evidenceDetails : map (text . T. unpack) (maybeToList $ definedAt evidenceVar)
390
+ vcat $
391
+ printDets evidenceSpan evidenceDetails : map (text . T. unpack) (maybeToList $ definedAt evidenceVar)
356
392
357
393
printDets :: RealSrcSpan -> Maybe (EvVarSource , Scope , Maybe Span ) -> SDoc
358
394
printDets _ Nothing = text " using an external instance"
359
395
printDets ospn (Just (src,_,mspn)) = pprSrc
360
396
$$ text " at" <+> text (T. unpack $ srcSpanToMdLink location)
361
397
where
362
- location = realSrcSpanToLocation $ traceShowId spn
398
+ location = realSrcSpanToLocation spn
363
399
-- Use the bind span if we have one, else use the occurrence span
364
400
spn = fromMaybe ospn mspn
365
401
pprSrc = case src of
0 commit comments