@@ -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,31 @@ 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
+ -- The evidence ghc generates is made up of a few primitives, like @WpLet@ (let bindings),
355
+ -- @WpEvLam@ (lambda abstractions) and so on.
356
+ -- The let binding refers to these lets.
357
+ --
358
+ -- For example, evidence for @Show ([Int], Bool)@ might look like:
359
+ --
360
+ -- @
361
+ -- $dShow,[]IntBool = $fShow,[]IntBool
362
+ -- -- indirection, we don't gain anything by printing this
363
+ -- $fShow,[]IntBool = $dShow, $fShow[]Int $fShowBool
364
+ -- -- This is the root "let" we render as a tree
365
+ -- $fShow[]Int = $dShow[] $fShowInt
366
+ -- -- second level let, collapse it into its parent $fShow,[]IntBool
367
+ -- $fShowInt = base:Data.Int.$dShowInt
368
+ -- -- indirection, remove it
369
+ -- $fShowBool = base:Data.Bool.$dShowBool
370
+ -- -- indirection, remove it
371
+ --
372
+ -- in $dShow,[]IntBool
373
+ -- @
374
+ --
375
+ -- On doing this we end up with the tree @Show ([Int], Bool) -> (Show (,), Show [], Show Int, Show Bool)@
376
+ --
377
+ -- It is also quite helpful to look at the @.hie@ file directly to see how the
378
+ -- evidence information is presented on disk. @hiedb dump <mod.hie>@
340
379
renderEvidenceTree (T. Node (EvidenceInfo {evidenceDetails= Just (EvLetBind _,_,_)}) [x])
341
380
= renderEvidenceTree x
342
381
renderEvidenceTree (T. Node (EvidenceInfo {evidenceDetails= Just (EvLetBind _,_,_), .. }) xs)
@@ -351,15 +390,15 @@ atPoint IdeOptions{} (HAR _ (hf :: HieASTs a) rf _ (kind :: HieKind hietype)) (D
351
390
= vcat (map renderEvidenceTree' xs)
352
391
renderEvidenceTree' (T. Node (EvidenceInfo {.. }) _)
353
392
= hang (text " - `" O. <> expandType evidenceType O. <> " `" ) 2 $
354
- vcat $
355
- printDets evidenceSpan evidenceDetails : map (text . T. unpack) (maybeToList $ definedAt evidenceVar)
393
+ vcat $
394
+ printDets evidenceSpan evidenceDetails : map (text . T. unpack) (maybeToList $ definedAt evidenceVar)
356
395
357
396
printDets :: RealSrcSpan -> Maybe (EvVarSource , Scope , Maybe Span ) -> SDoc
358
397
printDets _ Nothing = text " using an external instance"
359
398
printDets ospn (Just (src,_,mspn)) = pprSrc
360
399
$$ text " at" <+> text (T. unpack $ srcSpanToMdLink location)
361
400
where
362
- location = realSrcSpanToLocation $ traceShowId spn
401
+ location = realSrcSpanToLocation spn
363
402
-- Use the bind span if we have one, else use the occurrence span
364
403
spn = fromMaybe ospn mspn
365
404
pprSrc = case src of
0 commit comments