Skip to content

Commit

Permalink
Show other occurences of ambiguous label in warning
Browse files Browse the repository at this point in the history
  • Loading branch information
Julow committed Sep 1, 2021
1 parent 68f6a8a commit e5d075c
Show file tree
Hide file tree
Showing 4 changed files with 22 additions and 3 deletions.
4 changes: 4 additions & 0 deletions src/model/location_.ml
Original file line number Diff line number Diff line change
Expand Up @@ -25,3 +25,7 @@ let in_string s ~offset ~length s_span =
start = point_in_string s offset s_span.start;
end_ = point_in_string s (offset + length) s_span.start;
}

let pp_span_start fmt s =
Format.fprintf fmt "File \"%s\", line %d, character %d" s.file s.start.line
s.start.column
2 changes: 2 additions & 0 deletions src/model/location_.mli
Original file line number Diff line number Diff line change
Expand Up @@ -5,3 +5,5 @@ end
val set_end_as_offset_from_start : int -> span -> span

val in_string : string -> offset:int -> length:int -> span -> span

val pp_span_start : Format.formatter -> span -> unit
11 changes: 10 additions & 1 deletion src/xref2/link.ml
Original file line number Diff line number Diff line change
Expand Up @@ -28,6 +28,15 @@ let synopsis_of_module env (m : Component.Module.t) =
| Ok sg -> synopsis_from_comment (Component.extract_signature_doc sg)
| Error _ -> None)

let ambiguous_label_warning label_name labels =
let pp_label_loc fmt (`Label (_, x)) =
Location_.pp_span_start fmt (Location_.location x)
in
Lookup_failures.report_warning
"@[<2>Label '%s' is ambiguous. The other occurences are:@ %a@]" label_name
(Format.pp_print_list ~pp_sep:Format.pp_force_newline pp_label_loc)
labels

(** Duplicate labels are disambiguated by adding a "_2" suffix to them. The
order in which it is inserted into the env is used to decide which prefix to
assign, the first is unchanged.
Expand Down Expand Up @@ -57,7 +66,7 @@ let ensure_label_unique env heading =
| Error `Not_found -> heading (* Unexpected. *)
| Error (`Ambiguous (hd, tl)) -> (
if h.heading_label_explicit then
Lookup_failures.report_warning "Label '%s' is ambiguous." label_name;
ambiguous_label_warning label_name (hd :: tl);
match dup_index (hd :: tl) with
| 0 -> heading (* Don't update the first occurence. *)
| index ->
Expand Down
8 changes: 6 additions & 2 deletions test/xref2/v407_and_above/labels.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -6,9 +6,13 @@
Hint:
Define labels explicitly using the syntax '{1:explicit-label Heading text}'.
File "test.odoc":
Label 'B' is ambiguous.
Label 'B' is ambiguous. The other occurences are:
File "test.mli", line 16, character 6
File "test.mli", line 3, character 4
File "test.odoc":
Label 'B' is ambiguous.
Label 'B' is ambiguous. The other occurences are:
File "test.mli", line 10, character 6
File "test.mli", line 3, character 4

Labels:
Some are not in order because the 'doc' field appears after the rest in the output.
Expand Down

0 comments on commit e5d075c

Please sign in to comment.