aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/src/erl_parse.yrl
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/src/erl_parse.yrl')
-rw-r--r--lib/stdlib/src/erl_parse.yrl192
1 files changed, 72 insertions, 120 deletions
diff --git a/lib/stdlib/src/erl_parse.yrl b/lib/stdlib/src/erl_parse.yrl
index 928c10f7f2..002abc11e8 100644
--- a/lib/stdlib/src/erl_parse.yrl
+++ b/lib/stdlib/src/erl_parse.yrl
@@ -2,7 +2,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2011. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2012. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
@@ -26,7 +26,7 @@ attribute attr_val
function function_clauses function_clause
clause_args clause_guard clause_body
expr expr_100 expr_150 expr_160 expr_200 expr_300 expr_400 expr_500
-expr_600 expr_700 expr_800 expr_900
+expr_600 expr_700 expr_800
expr_max
list tail
list_comprehension lc_expr lc_exprs
@@ -253,15 +253,9 @@ expr_700 -> function_call : '$1'.
expr_700 -> record_expr : '$1'.
expr_700 -> expr_800 : '$1'.
-expr_800 -> expr_900 ':' expr_max :
+expr_800 -> expr_max ':' expr_max :
{remote,?line('$2'),'$1','$3'}.
-expr_800 -> expr_900 : '$1'.
-
-expr_900 -> '.' atom :
- {record_field,?line('$1'),{atom,?line('$1'),''},'$2'}.
-expr_900 -> expr_900 '.' atom :
- {record_field,?line('$2'),'$1','$3'}.
-expr_900 -> expr_max : '$1'.
+expr_800 -> expr_max : '$1'.
expr_max -> var : '$1'.
expr_max -> atomic : '$1'.
@@ -510,7 +504,7 @@ Erlang code.
-export([parse_form/1,parse_exprs/1,parse_term/1]).
-export([normalise/1,abstract/1,tokens/1,tokens/2]).
--export([abstract/2, package_segments/1]).
+-export([abstract/2]).
-export([inop_prec/1,preop_prec/1,func_prec/0,max_prec/0]).
-export([set_line/2,get_attribute/2,get_attributes/1]).
@@ -679,20 +673,6 @@ build_attribute({atom,La,module}, Val) ->
{attribute,La,module,Module};
[{atom,_Lm,Module},ExpList] ->
{attribute,La,module,{Module,var_list(ExpList)}};
- [Name] ->
- case package_segments(Name) of
- error ->
- error_bad_decl(La, module);
- Module ->
- {attribute,La,module,Module}
- end;
- [Name,ExpList] ->
- case package_segments(Name) of
- error ->
- error_bad_decl(La, module);
- Module ->
- {attribute,La,module,{Module,var_list(ExpList)}}
- end;
_Other ->
error_bad_decl(La, module)
end;
@@ -704,22 +684,8 @@ build_attribute({atom,La,export}, Val) ->
end;
build_attribute({atom,La,import}, Val) ->
case Val of
- [Name] ->
- case package_segments(Name) of
- error ->
- error_bad_decl(La, import);
- Module ->
- {attribute,La,import,Module}
- end;
[{atom,_Lm,Mod},ImpList] ->
{attribute,La,import,{Mod,farity_list(ImpList)}};
- [Name, ImpList] ->
- case package_segments(Name) of
- error ->
- error_bad_decl(La, import);
- Module ->
- {attribute,La,import,{Module,farity_list(ImpList)}}
- end;
_Other -> error_bad_decl(La, import)
end;
build_attribute({atom,La,record}, Val) ->
@@ -820,18 +786,6 @@ term(Expr) ->
catch _:_R -> ret_err(?line(Expr), "bad attribute")
end.
-package_segments(Name) ->
- package_segments(Name, [], []).
-
-package_segments({record_field, _, F1, F2}, Fs, As) ->
- package_segments(F1, [F2 | Fs], As);
-package_segments({atom, _, A}, [F | Fs], As) ->
- package_segments(F, Fs, [A | As]);
-package_segments({atom, _, A}, [], As) ->
- lists:reverse([A | As]);
-package_segments(_, _, _) ->
- error.
-
%% build_function([Clause]) -> {function,Line,Name,Arity,[Clause]}
build_function(Cs) ->
@@ -900,12 +854,6 @@ normalise({cons,_,Head,Tail}) ->
[normalise(Head)|normalise(Tail)];
normalise({tuple,_,Args}) ->
list_to_tuple(normalise_list(Args));
-%% Atom dot-notation, as in 'foo.bar.baz'
-normalise({record_field,_,_,_}=A) ->
- case package_segments(A) of
- error -> erlang:error({badarg, A});
- As -> list_to_atom(packages:concat(As))
- end;
%% Special case for unary +/-.
normalise({op,_,'+',{char,_,I}}) -> I;
normalise({op,_,'+',{integer,_,I}}) -> I;
@@ -923,73 +871,77 @@ normalise_list([]) ->
-spec abstract(Data) -> AbsTerm when
Data :: term(),
AbsTerm :: abstract_expr().
-abstract(T) when is_integer(T) -> {integer,0,T};
-abstract(T) when is_float(T) -> {float,0,T};
-abstract(T) when is_atom(T) -> {atom,0,T};
-abstract([]) -> {nil,0};
-abstract(B) when is_bitstring(B) ->
- {bin, 0, [abstract_byte(Byte, 0) || Byte <- bitstring_to_list(B)]};
-abstract([C|T]) when is_integer(C), 0 =< C, C < 256 ->
- abstract_string(T, [C]);
-abstract([H|T]) ->
- {cons,0,abstract(H),abstract(T)};
-abstract(Tuple) when is_tuple(Tuple) ->
- {tuple,0,abstract_list(tuple_to_list(Tuple))}.
-
-abstract_string([C|T], String) when is_integer(C), 0 =< C, C < 256 ->
- abstract_string(T, [C|String]);
-abstract_string([], String) ->
- {string, 0, lists:reverse(String)};
-abstract_string(T, String) ->
- not_string(String, abstract(T)).
-
-not_string([C|T], Result) ->
- not_string(T, {cons, 0, {integer, 0, C}, Result});
-not_string([], Result) ->
+abstract(T) ->
+ abstract(T, 0, epp:default_encoding()).
+
+%%% abstract/2 takes line and encoding options
+-spec abstract(Data, Options) -> AbsTerm when
+ Data :: term(),
+ Options :: Line | [Option],
+ Option :: {line, Line} | {encoding, Encoding},
+ Encoding :: latin1 | unicode | utf8,
+ Line :: erl_scan:line(),
+ AbsTerm :: abstract_expr().
+
+abstract(T, Line) when is_integer(Line) ->
+ abstract(T, Line, epp:default_encoding());
+abstract(T, Options) when is_list(Options) ->
+ Line = proplists:get_value(line, Options, 0),
+ Encoding = proplists:get_value(encoding, Options,epp:default_encoding()),
+ abstract(T, Line, Encoding).
+
+-define(UNICODE(C),
+ (C >= 0 andalso C < 16#D800 orelse
+ C > 16#DFFF andalso C < 16#FFFE orelse
+ C > 16#FFFF andalso C =< 16#10FFFF)).
+
+abstract(T, L, _E) when is_integer(T) -> {integer,L,T};
+abstract(T, L, _E) when is_float(T) -> {float,L,T};
+abstract(T, L, _E) when is_atom(T) -> {atom,L,T};
+abstract([], L, _E) -> {nil,L};
+abstract(B, L, _E) when is_bitstring(B) ->
+ {bin, L, [abstract_byte(Byte, L) || Byte <- bitstring_to_list(B)]};
+abstract([C|T], L, unicode=E) when ?UNICODE(C) ->
+ abstract_unicode_string(T, [C], L, E);
+abstract([C|T], L, utf8=E) when ?UNICODE(C) ->
+ abstract_unicode_string(T, [C], L, E);
+abstract([C|T], L, latin1=E) when is_integer(C), 0 =< C, C < 256 ->
+ abstract_string(T, [C], L, E);
+abstract([H|T], L, E) ->
+ {cons,L,abstract(H, L, E),abstract(T, L, E)};
+abstract(Tuple, L, E) when is_tuple(Tuple) ->
+ {tuple,L,abstract_list(tuple_to_list(Tuple), L, E)}.
+
+abstract_string([C|T], String, L, E) when is_integer(C), 0 =< C, C < 256 ->
+ abstract_string(T, [C|String], L, E);
+abstract_string([], String, L, _E) ->
+ {string, L, lists:reverse(String)};
+abstract_string(T, String, L, E) ->
+ not_string(String, abstract(T, L, E), L, E).
+
+abstract_unicode_string([C|T], String, L, E) when ?UNICODE(C) ->
+ abstract_unicode_string(T, [C|String], L, E);
+abstract_unicode_string([], String, L, _E) ->
+ {string, L, lists:reverse(String)};
+abstract_unicode_string(T, String, L, E) ->
+ not_string(String, abstract(T, L, E), L, E).
+
+not_string([C|T], Result, L, E) ->
+ not_string(T, {cons, L, {integer, L, C}, Result}, L, E);
+not_string([], Result, _L, _E) ->
Result.
-abstract_list([H|T]) ->
- [abstract(H)|abstract_list(T)];
-abstract_list([]) ->
+abstract_list([H|T], L, E) ->
+ [abstract(H, L, E)|abstract_list(T, L, E)];
+abstract_list([], _L, _E) ->
[].
-abstract_byte(Byte, Line) when is_integer(Byte) ->
- {bin_element, Line, {integer, Line, Byte}, default, default};
-abstract_byte(Bits, Line) ->
+abstract_byte(Byte, L) when is_integer(Byte) ->
+ {bin_element, L, {integer, L, Byte}, default, default};
+abstract_byte(Bits, L) ->
Sz = bit_size(Bits),
<<Val:Sz>> = Bits,
- {bin_element, Line, {integer, Line, Val}, {integer, Line, Sz}, default}.
-
-%%% abstract/2 keeps the line number
-abstract(T, Line) when is_integer(T) -> {integer,Line,T};
-abstract(T, Line) when is_float(T) -> {float,Line,T};
-abstract(T, Line) when is_atom(T) -> {atom,Line,T};
-abstract([], Line) -> {nil,Line};
-abstract(B, Line) when is_bitstring(B) ->
- {bin, Line, [abstract_byte(Byte, Line) || Byte <- bitstring_to_list(B)]};
-abstract([C|T], Line) when is_integer(C), 0 =< C, C < 256 ->
- abstract_string(T, [C], Line);
-abstract([H|T], Line) ->
- {cons,Line,abstract(H, Line),abstract(T, Line)};
-abstract(Tuple, Line) when is_tuple(Tuple) ->
- {tuple,Line,abstract_list(tuple_to_list(Tuple), Line)}.
-
-abstract_string([C|T], String, Line) when is_integer(C), 0 =< C, C < 256 ->
- abstract_string(T, [C|String], Line);
-abstract_string([], String, Line) ->
- {string, Line, lists:reverse(String)};
-abstract_string(T, String, Line) ->
- not_string(String, abstract(T, Line), Line).
-
-not_string([C|T], Result, Line) ->
- not_string(T, {cons, Line, {integer, Line, C}, Result}, Line);
-not_string([], Result, _Line) ->
- Result.
-
-abstract_list([H|T], Line) ->
- [abstract(H, Line)|abstract_list(T, Line)];
-abstract_list([], _Line) ->
- [].
+ {bin_element, L, {integer, L, Val}, {integer, L, Sz}, default}.
%% Generate a list of tokens representing the abstract term.
@@ -1079,9 +1031,9 @@ preop_prec('#') -> {700,800}.
func_prec() -> {800,700}.
--spec max_prec() -> 1000.
+-spec max_prec() -> 900.
-max_prec() -> 1000.
+max_prec() -> 900.
%%% [Experimental]. The parser just copies the attributes of the
%%% scanner tokens to the abstract format. This design decision has