Skip to content

Commit

Permalink
Error source highlighting: align using tabs to match tabs in the source
Browse files Browse the repository at this point in the history
Fixes #9116
  • Loading branch information
Armaël Guéneau committed Nov 13, 2019
1 parent 7e842f6 commit 1449d92
Show file tree
Hide file tree
Showing 2 changed files with 12 additions and 6 deletions.
16 changes: 11 additions & 5 deletions parsing/location.ml
Original file line number Diff line number Diff line change
Expand Up @@ -463,21 +463,27 @@ let highlight_quote ppf
(* Single-line error *)
Format.fprintf ppf "%s | %s@," line_nb line;
Format.fprintf ppf "%*s " (String.length line_nb) "";
for pos = line_start_cnum to rightmost.pos_cnum - 1 do
String.iteri (fun i c ->
let pos = line_start_cnum + i in
if ISet.is_start iset ~pos <> None then
Format.fprintf ppf "@{<%s>" highlight_tag;
if ISet.mem iset ~pos then Format.pp_print_char ppf '^'
else Format.pp_print_char ppf ' ';
else if pos < rightmost.pos_cnum then begin
(* For alignment purposes, align using a tab for each tab in the
source code *)
if c = '\t' then Format.pp_print_char ppf '\t'
else Format.pp_print_char ppf ' '
end;
if ISet.is_end iset ~pos <> None then
Format.fprintf ppf "@}"
done;
) line;
Format.fprintf ppf "@}@,"
| _ ->
(* Multi-line error *)
Misc.pp_two_columns ~sep:"|" ~max_lines ppf
@@ List.map (fun (line, line_nb, line_start_cnum) ->
let line = String.mapi (fun i car ->
if ISet.mem iset ~pos:(line_start_cnum + i) then car else '.'
let line = String.mapi (fun i c ->
if ISet.mem iset ~pos:(line_start_cnum + i) then c else '.'
) line in
(line_nb, line)
) lines
Expand Down
2 changes: 1 addition & 1 deletion testsuite/tests/messages/highlight_tabs.ml
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@
[%%expect{|
Line 1, characters 10-13:
1 | let x = abc
^^^
^^^
Error: Unbound value abc
Hint: Did you mean abs?
|}];;

0 comments on commit 1449d92

Please sign in to comment.