Skip to content

Commit 71218c8

Browse files
panglesdjonludlam
authored andcommitted
Do not add anchors to ghost locations from uid_to_loc table
Signed-off-by: Paul-Elliot <[email protected]>
1 parent 6bd0fc3 commit 71218c8

File tree

1 file changed

+27
-23
lines changed

1 file changed

+27
-23
lines changed

src/loader/implementation.ml

Lines changed: 27 additions & 23 deletions
Original file line numberDiff line numberDiff line change
@@ -432,30 +432,34 @@ let of_cmt (source_id_opt : Odoc_model.Paths.Identifier.SourcePage.t option)
432432
Odoc_model.Paths.Identifier.SourceLocation.t Shape.Uid.Map.t =
433433
Shape.Uid.Map.filter_map
434434
(fun uid loc ->
435-
let identifier = Ident_env.identifier_of_loc env loc in
436-
let anchor =
437-
match identifier with
438-
| Some x ->
435+
if loc.Location.loc_ghost then None
436+
else
437+
let identifier = Ident_env.identifier_of_loc env loc in
438+
let anchor =
439+
match identifier with
440+
| Some x ->
441+
Some
442+
(Odoc_model.Names.DefName.make_std
443+
(anchor_of_identifier x))
444+
| None -> (
445+
match uid with
446+
| Compilation_unit _ -> None
447+
| Item _ ->
448+
let name =
449+
Odoc_model.Names.DefName.make_std
450+
(Printf.sprintf "def_%d_%d" loc.loc_start.pos_cnum
451+
loc.loc_end.pos_cnum)
452+
in
453+
Some name
454+
| _ -> None)
455+
in
456+
match anchor with
457+
| Some a ->
439458
Some
440-
(Odoc_model.Names.DefName.make_std (anchor_of_identifier x))
441-
| None -> (
442-
match uid with
443-
| Compilation_unit _ -> None
444-
| Item _ ->
445-
let name =
446-
Odoc_model.Names.DefName.make_std
447-
(Printf.sprintf "def_%d_%d" loc.loc_start.pos_cnum
448-
loc.loc_end.pos_cnum)
449-
in
450-
Some name
451-
| _ -> None)
452-
in
453-
match anchor with
454-
| Some a ->
455-
Some
456-
(Odoc_model.Paths.Identifier.Mk.source_location (source_id, a)
457-
:> Odoc_model.Paths.Identifier.SourceLocation.t)
458-
| None -> None)
459+
(Odoc_model.Paths.Identifier.Mk.source_location
460+
(source_id, a)
461+
:> Odoc_model.Paths.Identifier.SourceLocation.t)
462+
| None -> None)
459463
uid_to_loc_map
460464
in
461465

0 commit comments

Comments
 (0)