Skip to content

Commit cfd73c7

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

File tree

1 file changed

+48
-9
lines changed

1 file changed

+48
-9
lines changed

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

Lines changed: 48 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -269,12 +269,26 @@ atPoint IdeOptions{} (HAR _ (hf :: HieASTs a) rf _ (kind :: HieKind hietype)) (D
269269
prettyName :: (Either ModuleName Name, IdentifierDetails hietype) -> IO T.Text
270270
prettyName (Right n, dets)
271271
-- 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
278292
where maybeKind = fmap printOutputable $ safeTyThingType =<< lookupNameEnv km n
279293
pretty Nothing Nothing = Nothing
280294
pretty (Just define) Nothing = Just $ define <> "\n"
@@ -337,6 +351,31 @@ atPoint IdeOptions{} (HAR _ (hf :: HieASTs a) rf _ (kind :: HieKind hietype)) (D
337351
renderEvidenceTree :: Tree (EvidenceInfo a) -> SDoc
338352
-- However, if the root constraint is simply a<n indirection (via let) to a single other constraint,
339353
-- 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>@
340379
renderEvidenceTree (T.Node (EvidenceInfo{evidenceDetails=Just (EvLetBind _,_,_)}) [x])
341380
= renderEvidenceTree x
342381
renderEvidenceTree (T.Node (EvidenceInfo{evidenceDetails=Just (EvLetBind _,_,_), ..}) xs)
@@ -351,15 +390,15 @@ atPoint IdeOptions{} (HAR _ (hf :: HieASTs a) rf _ (kind :: HieKind hietype)) (D
351390
= vcat (map renderEvidenceTree' xs)
352391
renderEvidenceTree' (T.Node (EvidenceInfo{..}) _)
353392
= 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)
356395

357396
printDets :: RealSrcSpan -> Maybe (EvVarSource, Scope, Maybe Span) -> SDoc
358397
printDets _ Nothing = text "using an external instance"
359398
printDets ospn (Just (src,_,mspn)) = pprSrc
360399
$$ text "at" <+> text (T.unpack $ srcSpanToMdLink location)
361400
where
362-
location = realSrcSpanToLocation $ traceShowId spn
401+
location = realSrcSpanToLocation spn
363402
-- Use the bind span if we have one, else use the occurrence span
364403
spn = fromMaybe ospn mspn
365404
pprSrc = case src of

0 commit comments

Comments
 (0)