Skip to content

Commit

Permalink
Also preserve user newlines if trailing commas exist
Browse files Browse the repository at this point in the history
  • Loading branch information
José Valim committed Oct 9, 2017
1 parent dd4fd6a commit 9b5af33
Show file tree
Hide file tree
Showing 3 changed files with 95 additions and 15 deletions.
18 changes: 9 additions & 9 deletions lib/elixir/src/elixir_parser.yrl
Original file line number Diff line number Diff line change
Expand Up @@ -362,19 +362,19 @@ close_paren -> eol ')' : '$2'.
empty_paren -> open_paren ')' : '$1'.

open_bracket -> '[' : '$1'.
open_bracket -> '[' eol : set_eol('$1').
open_bracket -> '[' eol : next_is_eol('$1').
close_bracket -> ']' : '$1'.
close_bracket -> eol ']' : set_eol('$2').
close_bracket -> eol ']' : '$2'.

open_bit -> '<<' : '$1'.
open_bit -> '<<' eol : set_eol('$1').
open_bit -> '<<' eol : next_is_eol('$1').
close_bit -> '>>' : '$1'.
close_bit -> eol '>>' : set_eol('$2').
close_bit -> eol '>>' : '$2'.

open_curly -> '{' : '$1'.
open_curly -> '{' eol : set_eol('$1').
open_curly -> '{' eol : next_is_eol('$1').
close_curly -> '}' : '$1'.
close_curly -> eol '}' : set_eol('$2').
close_curly -> eol '}' : '$2'.

% Operators

Expand Down Expand Up @@ -425,7 +425,7 @@ when_op_eol -> when_op : '$1'.
when_op_eol -> when_op eol : '$1'.

stab_op_eol -> stab_op : '$1'.
stab_op_eol -> stab_op eol : set_eol('$1').
stab_op_eol -> stab_op eol : next_is_eol('$1').

at_op_eol -> at_op : '$1'.
at_op_eol -> at_op eol : '$1'.
Expand All @@ -437,7 +437,7 @@ rel_op_eol -> rel_op : '$1'.
rel_op_eol -> rel_op eol : '$1'.

arrow_op_eol -> arrow_op : '$1'.
arrow_op_eol -> arrow_op eol : set_eol('$1').
arrow_op_eol -> arrow_op eol : next_is_eol('$1').

% Dot operator

Expand Down Expand Up @@ -737,7 +737,7 @@ eol_op(Token) ->
[]
end.

set_eol(Token) ->
next_is_eol(Token) ->
{Line, Column, _} = ?location(Token),
setelement(2, Token, {Line, Column, eol}).

Expand Down
19 changes: 14 additions & 5 deletions lib/elixir/src/elixir_tokenizer.erl
Original file line number Diff line number Diff line change
Expand Up @@ -325,15 +325,22 @@ tokenize([$, | Rest], Line, Column, Scope, Tokens) ->
Token = {',', {Line, {Column, Column + 1}, 0}},
handle_terminator(Rest, Line, Column + 1, Scope, Token, Tokens);

tokenize([T, T | Rest], Line, Column, Scope, Tokens) when T == $<; T == $> ->
Token = {list_to_atom([T, T]), {Line, {Column, Column + 2}, nil}},
tokenize([$<, $< | Rest], Line, Column, Scope, Tokens) ->
Token = {'<<', {Line, {Column, Column + 2}, nil}},
handle_terminator(Rest, Line, Column + 2, Scope, Token, Tokens);

tokenize([T | Rest], Line, Column, Scope, Tokens) when T == $(;
T == ${; T == $}; T == $[; T == $]; T == $) ->
tokenize([$>, $> | Rest], Line, Column, Scope, Tokens) ->
Token = {'>>', {Line, {Column, Column + 2}, previous_was_eol(Tokens)}},
handle_terminator(Rest, Line, Column + 2, Scope, Token, Tokens);

tokenize([T | Rest], Line, Column, Scope, Tokens) when T == $(; T == ${; T == $[ ->
Token = {list_to_atom([T]), {Line, {Column, Column + 1}, nil}},
handle_terminator(Rest, Line, Column + 1, Scope, Token, Tokens);

tokenize([T | Rest], Line, Column, Scope, Tokens) when T == $); T == $}; T == $] ->
Token = {list_to_atom([T]), {Line, {Column, Column + 1}, previous_was_eol(Tokens)}},
handle_terminator(Rest, Line, Column + 1, Scope, Token, Tokens);

% ## Two Token Operators
tokenize([T1, T2 | Rest], Line, Column, Scope, Tokens) when ?two_op(T1, T2) ->
handle_op(Rest, Line, Column, two_op, 2, list_to_atom([T1, T2]), Scope, Tokens);
Expand Down Expand Up @@ -993,7 +1000,9 @@ add_token_with_eol({unary_op, _, _} = Left, T) -> [Left | T];
add_token_with_eol(Left, [{eol, _} | T]) -> [Left | T];
add_token_with_eol(Left, T) -> [Left | T].

previous_was_eol([{eol, _} | _]) -> eol;
previous_was_eol([{',', {_, _, Count}} | _]) when Count > 0 -> eol;
previous_was_eol([{';', {_, _, Count}} | _]) when Count > 0 -> eol;
previous_was_eol([{eol, {_, _, Count}} | _]) when Count > 0 -> eol;
previous_was_eol(_) -> nil.

%% Error handling
Expand Down
73 changes: 72 additions & 1 deletion lib/elixir/test/elixir/code_formatter/containers_test.exs
Original file line number Diff line number Diff line change
Expand Up @@ -62,6 +62,24 @@ defmodule Code.Formatter.ContainersTest do
# Doesn't preserve this because only the beginning has a newline
assert_format "{\nfoo, bar, baz}", "{foo, bar, baz}"
end

test "preserves user choice even when it fits with trailing comma" do
bad = """
{
:hello,
:foo,
:bar,
}
"""

assert_format bad, """
{
:hello,
:foo,
:bar
}
"""
end
end

describe "lists" do
Expand Down Expand Up @@ -168,6 +186,24 @@ defmodule Code.Formatter.ContainersTest do
# Doesn't preserve this because only the beginning has a newline
assert_format "[\nfoo, bar, baz]", "[foo, bar, baz]"
end

test "preserves user choice even when it fits with trailing comma" do
bad = """
[
:hello,
:foo,
:bar,
]
"""

assert_format bad, """
[
:hello,
:foo,
:bar
]
"""
end
end

describe "bitstrings" do
Expand Down Expand Up @@ -223,6 +259,24 @@ defmodule Code.Formatter.ContainersTest do
# Doesn't preserve this because only the beginning has a newline
assert_format "<<\nfoo, bar, baz>>", "<<foo, bar, baz>>"
end

test "preserves user choice even when it fits with trailing comma" do
bad = """
<<
:hello,
:foo,
:bar,
>>
"""

assert_format bad, """
<<
:hello,
:foo,
:bar
>>
"""
end
end

describe "maps" do
Expand Down Expand Up @@ -308,6 +362,24 @@ defmodule Code.Formatter.ContainersTest do
# Doesn't preserve this because only the beginning has a newline
assert_format "%{\nfoo: 1, bar: 2}", "%{foo: 1, bar: 2}"
end

test "preserves user choice even when it fits with trailing comma" do
bad = """
%{
:hello,
:foo,
:bar,
}
"""

assert_format bad, """
%{
:hello,
:foo,
:bar
}
"""
end
end

describe "maps with update" do
Expand Down Expand Up @@ -355,7 +427,6 @@ defmodule Code.Formatter.ContainersTest do
end
end


describe "structs" do
test "without arguments" do
assert_format "%struct{ }", "%struct{}"
Expand Down

0 comments on commit 9b5af33

Please sign in to comment.