Skip to content

Commit

Permalink
Ensure underlining indents by code points, not bytes
Browse files Browse the repository at this point in the history
  • Loading branch information
richcarl committed Feb 4, 2021
1 parent 1a9bf7b commit ce1ea49
Showing 1 changed file with 16 additions and 11 deletions.
27 changes: 16 additions & 11 deletions lib/compiler/src/sys_messages.erl
Original file line number Diff line number Diff line change
Expand Up @@ -95,23 +95,27 @@ quote_source_1(File, Loc1, Line) when is_integer(Line) ->
quote_source_1(File, {StartLine, StartCol}, {EndLine, EndCol}) ->
case file:read_file(File) of
{ok, Bin} ->
Enc = case epp:read_encoding_from_binary(Bin) of
none -> epp:default_encoding();
Enc0 -> Enc0
end,
Ctx =
if
StartLine =:= EndLine -> 0;
true -> 1
end,
case seek_line(Bin, 1, StartLine - Ctx) of
{ok, Bin1} ->
quote_source_2(Bin1, StartLine, StartCol, EndLine, EndCol, Ctx);
quote_source_2(Bin1, Enc, StartLine, StartCol, EndLine, EndCol, Ctx);
error ->
""
end;
{error, _} ->
""
end.

quote_source_2(Bin, StartLine, StartCol, EndLine, EndCol, Ctx) ->
case take_lines(Bin, StartLine - Ctx, EndLine + Ctx) of
quote_source_2(Bin, Enc, StartLine, StartCol, EndLine, EndCol, Ctx) ->
case take_lines(Bin, Enc, StartLine - Ctx, EndLine + Ctx) of
[] ->
"";
Lines ->
Expand All @@ -137,7 +141,7 @@ line_prefix() ->
"% ".

fmt_line(L, Text) ->
io_lib:format("~ts~4.ts| ~ts\n", [line_prefix(), line_to_txt(L), Text]).
[line_prefix(), io_lib:format("~4.ts| ", [line_to_txt(L)]), Text, "\n"].

line_to_txt(0) -> "";
line_to_txt(L) -> integer_to_list(L).
Expand Down Expand Up @@ -173,9 +177,9 @@ underline(Text, Start, Start) ->
underline(Text, Start, End) ->
underline(Text, Start, End, 1).

underline(<<$\t, Text/binary>>, Start, End, N) when N < Start ->
underline([$\t | Text], Start, End, N) when N < Start ->
[$\t | underline(Text, Start, End, N + 1)];
underline(<<_, Text/binary>>, Start, End, N) when N < Start ->
underline([_ | Text], Start, End, N) when N < Start ->
[$\s | underline(Text, Start, End, N + 1)];
underline(_Text, _Start, End, N) ->
underline_1(N, End).
Expand All @@ -191,12 +195,13 @@ seek_line(<<$\r, $\n, Rest/binary>>, N, L) -> seek_line(Rest, N + 1, L);
seek_line(<<_, Rest/binary>>, N, L) -> seek_line(Rest, N, L);
seek_line(<<>>, _, _) -> error.

take_lines(<<>>, _Here, _To) ->
take_lines(<<>>, _Enc, _Here, _To) ->
[];
take_lines(Bin, Here, To) when Here =< To ->
{Line, Rest} = take_line(Bin, <<>>),
[{Here, Line} | take_lines(Rest, Here + 1, To)];
take_lines(_Bin, _Here, _To) ->
take_lines(Bin, Enc, Here, To) when Here =< To ->
{Text, Rest} = take_line(Bin, <<>>),
[{Here, unicode:characters_to_list(Text, Enc)}
| take_lines(Rest, Enc, Here + 1, To)];
take_lines(_Bin, _Enc, _Here, _To) ->
[].

take_line(<<$\n, Rest/binary>>, Ack) ->
Expand Down

0 comments on commit ce1ea49

Please sign in to comment.