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.yrl97
1 files changed, 52 insertions, 45 deletions
diff --git a/lib/stdlib/src/erl_parse.yrl b/lib/stdlib/src/erl_parse.yrl
index 6316db7054..1d4a2a1fef 100644
--- a/lib/stdlib/src/erl_parse.yrl
+++ b/lib/stdlib/src/erl_parse.yrl
@@ -2,7 +2,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 1996-2013. All Rights Reserved.
+%% Copyright Ericsson AB 1996-2014. 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
@@ -753,6 +753,9 @@ attribute_farity({cons,L,H,T}) ->
attribute_farity({tuple,L,Args0}) ->
Args = attribute_farity_list(Args0),
{tuple,L,Args};
+attribute_farity({map,L,Args0}) ->
+ Args = attribute_farity_map(Args0),
+ {map,L,Args};
attribute_farity({op,L,'/',{atom,_,_}=Name,{integer,_,_}=Arity}) ->
{tuple,L,[Name,Arity]};
attribute_farity(Other) -> Other.
@@ -760,6 +763,10 @@ attribute_farity(Other) -> Other.
attribute_farity_list(Args) ->
[attribute_farity(A) || A <- Args].
+%% It is not meaningful to have farity keys.
+attribute_farity_map(Args) ->
+ [{Op,L,K,attribute_farity(V)} || {Op,L,K,V} <- Args].
+
-spec error_bad_decl(integer(), attributes()) -> no_return().
error_bad_decl(L, S) ->
@@ -848,10 +855,12 @@ build_fun(Line, Cs) ->
end.
check_clauses(Cs, Name, Arity) ->
- mapl(fun ({clause,L,N,As,G,B}) when N =:= Name, length(As) =:= Arity ->
- {clause,L,As,G,B};
- ({clause,L,_N,_As,_G,_B}) ->
- ret_err(L, "head mismatch") end, Cs).
+ [case C of
+ {clause,L,N,As,G,B} when N =:= Name, length(As) =:= Arity ->
+ {clause,L,As,G,B};
+ {clause,L,_N,_As,_G,_B} ->
+ ret_err(L, "head mismatch")
+ end || C <- Cs].
build_try(L,Es,Scs,{Ccs,As}) ->
{'try',L,Es,Scs,Ccs,As}.
@@ -861,17 +870,6 @@ ret_err(L, S) ->
{location,Location} = get_attribute(L, location),
return_error(Location, S).
-%% mapl(F,List)
-%% an alternative map which always maps from left to right
-%% and makes it possible to interrupt the mapping with throw on
-%% the first occurence from left as expected.
-%% can be removed when the jam machine (and all other machines)
-%% uses the standardized (Erlang 5.0) evaluation order (from left to right)
-mapl(F, [H|T]) ->
- V = F(H),
- [V | mapl(F,T)];
-mapl(_, []) ->
- [].
%% Convert between the abstract form of a term and a term.
@@ -919,59 +917,65 @@ normalise_list([]) ->
Data :: term(),
AbsTerm :: abstract_expr().
abstract(T) ->
- abstract(T, 0, epp:default_encoding()).
+ abstract(T, 0, enc_func(epp:default_encoding())).
+
+-type encoding_func() :: fun((non_neg_integer()) -> boolean()).
%%% 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,
+ Encoding :: 'latin1' | 'unicode' | 'utf8' | 'none' | encoding_func(),
Line :: erl_scan:line(),
AbsTerm :: abstract_expr().
abstract(T, Line) when is_integer(Line) ->
- abstract(T, Line, epp:default_encoding());
+ abstract(T, Line, enc_func(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).
+ EncFunc = enc_func(Encoding),
+ abstract(T, Line, EncFunc).
-define(UNICODE(C),
- is_integer(C) andalso
- (C >= 0 andalso C < 16#D800 orelse
+ (C < 16#D800 orelse
C > 16#DFFF andalso C < 16#FFFE orelse
C > 16#FFFF andalso C =< 16#10FFFF)).
+enc_func(latin1) -> fun(C) -> C < 256 end;
+enc_func(unicode) -> fun(C) -> ?UNICODE(C) end;
+enc_func(utf8) -> fun(C) -> ?UNICODE(C) end;
+enc_func(none) -> none;
+enc_func(Fun) when is_function(Fun, 1) -> Fun;
+enc_func(Term) -> erlang:error({badarg, Term}).
+
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) ->
+abstract([H|T], L, none=E) ->
{cons,L,abstract(H, L, E),abstract(T, L, E)};
+abstract(List, L, E) when is_list(List) ->
+ abstract_list(List, [], 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) ->
+ {tuple,L,abstract_tuple_list(tuple_to_list(Tuple), L, E)};
+abstract(Map, L, E) when is_map(Map) ->
+ {map,L,abstract_map_fields(maps:to_list(Map),L,E)}.
+
+abstract_list([H|T], String, L, E) ->
+ case is_integer(H) andalso H >= 0 andalso E(H) of
+ true ->
+ abstract_list(T, [H|String], L, E);
+ false ->
+ AbstrList = {cons,L,abstract(H, L, E),abstract(T, L, E)},
+ not_string(String, AbstrList, L, E)
+ end;
+abstract_list([], String, L, _E) ->
{string, L, lists:reverse(String)};
-abstract_unicode_string(T, String, L, E) ->
+abstract_list(T, String, L, E) ->
not_string(String, abstract(T, L, E), L, E).
not_string([C|T], Result, L, E) ->
@@ -979,11 +983,14 @@ not_string([C|T], Result, L, E) ->
not_string([], Result, _L, _E) ->
Result.
-abstract_list([H|T], L, E) ->
- [abstract(H, L, E)|abstract_list(T, L, E)];
-abstract_list([], _L, _E) ->
+abstract_tuple_list([H|T], L, E) ->
+ [abstract(H, L, E)|abstract_tuple_list(T, L, E)];
+abstract_tuple_list([], _L, _E) ->
[].
+abstract_map_fields(Fs,L,E) ->
+ [{map_field_assoc,L,abstract(K,L,E),abstract(V,L,E)}||{K,V}<-Fs].
+
abstract_byte(Byte, L) when is_integer(Byte) ->
{bin_element, L, {integer, L, Byte}, default, default};
abstract_byte(Bits, L) ->