Skip to content

Commit bc06c34

Browse files
committed
Single pass
1 parent 38d52c7 commit bc06c34

File tree

1 file changed

+18
-31
lines changed

1 file changed

+18
-31
lines changed

lib/elixir/src/elixir_parser.yrl

Lines changed: 18 additions & 31 deletions
Original file line numberDiff line numberDiff line change
@@ -672,15 +672,15 @@ meta_from_location({Line, Column, _}) ->
672672
do_end_meta(Do, End) ->
673673
case ?token_metadata() of
674674
true ->
675-
[{do, meta_from_location(?location(Do))}, {'end', meta_from_location(?location(End))}];
675+
[{do, meta_from_token(Do)}, {'end', meta_from_token(End)}];
676676
false ->
677677
[]
678678
end.
679679

680680
meta_from_token_with_closing(Begin, End) ->
681681
case ?token_metadata() of
682682
true ->
683-
[{closing, meta_from_location(?location(End))} | meta_from_token(Begin)];
683+
[{closing, meta_from_token(End)} | meta_from_token(Begin)];
684684
false ->
685685
meta_from_token(Begin)
686686
end.
@@ -778,46 +778,33 @@ build_map_update(Left, {Pipe, Struct, Map}, Right, Extra) ->
778778

779779
%% Blocks
780780

781-
build_block(Exprs) -> build_block(Exprs, []).
781+
build_block(Exprs) -> build_block(Exprs, {}).
782782

783-
build_block([{unquote_splicing, _, [_]}]=Exprs, Meta) ->
784-
{'__block__', Meta, Exprs};
785-
build_block([{Op, ExprMeta, Args}], Meta) ->
783+
build_block([{unquote_splicing, _, [_]}]=Exprs, BeforeAfter) ->
784+
{'__block__', block_meta(BeforeAfter), Exprs};
785+
build_block([{Op, ExprMeta, Args}], {Before, After}) ->
786786
ExprMetaWithExtra =
787787
case ?token_metadata() of
788-
true -> ExprMeta ++ block_meta(Meta);
789-
false -> ExprMeta
788+
true ->
789+
ExprMeta ++ [{parens_opening, meta_from_token(Before)}, {parens_closing, meta_from_token(After)}];
790+
false ->
791+
ExprMeta
790792
end,
791793
{Op, ExprMetaWithExtra, Args};
792-
build_block([Expr], _Meta) ->
794+
build_block([Expr], _BeforeAfter) ->
793795
Expr;
794-
build_block(Exprs, Meta) ->
795-
{'__block__', Meta, Exprs}.
796-
797-
block_meta(Meta) ->
798-
block_meta(Meta, [], []).
799-
800-
block_meta([], [], []) ->
801-
[];
802-
block_meta([], [], Closing) ->
803-
[{parens_closing, Closing}];
804-
block_meta([], Opening, Closing) ->
805-
[{parens_opening, lists:reverse(Opening)} | block_meta([], [], Closing)];
806-
block_meta([{line, Line} | Meta], Opening, Closing) ->
807-
block_meta(Meta, [{line, Line} | Opening], Closing);
808-
block_meta([{column, Column} | Meta], Opening, Closing) ->
809-
block_meta(Meta, [{column, Column} | Opening], Closing);
810-
block_meta([{closing, Closing} | Meta], Opening, _Closing) ->
811-
block_meta(Meta, Opening, Closing);
812-
block_meta([_ | Meta], Opening, Closing) ->
813-
block_meta(Meta, Opening, Closing).
796+
build_block(Exprs, BeforeAfter) ->
797+
{'__block__', block_meta(BeforeAfter), Exprs}.
798+
799+
block_meta({}) -> [];
800+
block_meta({Before, After}) -> meta_from_token_with_closing(Before, After).
814801

815802
%% Newlines
816803

817804
newlines_pair(Left, Right) ->
818805
case ?token_metadata() of
819806
true ->
820-
newlines(?location(Left), [{closing, meta_from_location(?location(Right))}]);
807+
newlines(?location(Left), [{closing, meta_from_token(Right)}]);
821808
false ->
822809
[]
823810
end.
@@ -1089,7 +1076,7 @@ build_paren_stab(_Before, [{Op, _, [_]}]=Exprs, _After) when ?rearrange_uop(Op)
10891076
{'__block__', [], Exprs};
10901077
build_paren_stab(Before, Stab, After) ->
10911078
case check_stab(Stab, none) of
1092-
block -> build_block(reverse(Stab), meta_from_token_with_closing(Before, After));
1079+
block -> build_block(reverse(Stab), {Before, After});
10931080
stab -> handle_literal(collect_stab(Stab, [], []), Before, newlines_pair(Before, After))
10941081
end.
10951082

0 commit comments

Comments
 (0)