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.yrl39
1 files changed, 35 insertions, 4 deletions
diff --git a/lib/stdlib/src/erl_parse.yrl b/lib/stdlib/src/erl_parse.yrl
index 15b45d72f4..bd5d65a1e1 100644
--- a/lib/stdlib/src/erl_parse.yrl
+++ b/lib/stdlib/src/erl_parse.yrl
@@ -511,6 +511,15 @@ Erlang code.
%% of the generated .erl file by the HiPE compiler. Please do not remove.
-compile([{hipe,[{regalloc,linear_scan}]}]).
+-export_type([abstract_clause/0, abstract_expr/0, abstract_form/0,
+ error_info/0]).
+
+-type abstract_clause() :: term().
+-type abstract_expr() :: term().
+-type abstract_form() :: term().
+-type error_description() :: term().
+-type error_info() :: {erl_scan:line(), module(), error_description()}.
+-type token() :: {Tag :: atom(), Line :: erl_scan:line()}.
%% mkop(Op, Arg) -> {op,Line,Op,Arg}.
%% mkop(Left, Op, Right) -> {op,Line,Op,Left,Right}.
@@ -534,11 +543,19 @@ Erlang code.
%% These really suck and are only here until Calle gets multiple
%% entry points working.
+-spec parse_form(Tokens) -> {ok, AbsForm} | {error, ErrorInfo} when
+ Tokens :: [token()],
+ AbsForm :: abstract_form(),
+ ErrorInfo :: error_info().
parse_form([{'-',L1},{atom,L2,spec}|Tokens]) ->
parse([{'-',L1},{'spec',L2}|Tokens]);
parse_form(Tokens) ->
parse(Tokens).
+-spec parse_exprs(Tokens) -> {ok, ExprList} | {error, ErrorInfo} when
+ Tokens :: [token()],
+ ExprList :: [abstract_expr()],
+ ErrorInfo :: error_info().
parse_exprs(Tokens) ->
case parse([{atom,0,f},{'(',0},{')',0},{'->',0}|Tokens]) of
{ok,{function,_Lf,f,0,[{clause,_Lc,[],[],Exprs}]}} ->
@@ -546,6 +563,10 @@ parse_exprs(Tokens) ->
{error,_} = Err -> Err
end.
+-spec parse_term(Tokens) -> {ok, Term} | {error, ErrorInfo} when
+ Tokens :: [token()],
+ Term :: term(),
+ ErrorInfo :: error_info().
parse_term(Tokens) ->
case parse([{atom,0,f},{'(',0},{')',0},{'->',0}|Tokens]) of
{ok,{function,_Lf,f,0,[{clause,_Lc,[],[],[Expr]}]}} ->
@@ -830,6 +851,7 @@ check_clauses(Cs, Name, Arity) ->
build_try(L,Es,Scs,{Ccs,As}) ->
{'try',L,Es,Scs,Ccs,As}.
+-spec ret_err(_, _) -> no_return().
ret_err(L, S) ->
{location,Location} = get_attribute(L, location),
return_error(Location, S).
@@ -846,10 +868,11 @@ mapl(F, [H|T]) ->
mapl(_, []) ->
[].
-%% normalise(AbsTerm)
-%% abstract(Term)
%% Convert between the abstract form of a term and a term.
+-spec normalise(AbsTerm) -> Data when
+ AbsTerm :: abstract_expr(),
+ Data :: term().
normalise({char,_,C}) -> C;
normalise({integer,_,I}) -> I;
normalise({float,_,F}) -> F;
@@ -887,6 +910,9 @@ normalise_list([H|T]) ->
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};
@@ -955,13 +981,18 @@ abstract_list([H|T], Line) ->
abstract_list([], _Line) ->
[].
-%% tokens(AbsTerm) -> [Token]
-%% tokens(AbsTerm, More) -> [Token]
%% Generate a list of tokens representing the abstract term.
+-spec tokens(AbsTerm) -> Tokens when
+ AbsTerm :: abstract_expr(),
+ Tokens :: [token()].
tokens(Abs) ->
tokens(Abs, []).
+-spec tokens(AbsTerm, MoreTokens) -> Tokens when
+ AbsTerm :: abstract_expr(),
+ MoreTokens :: [token()],
+ Tokens :: [token()].
tokens({char,L,C}, More) -> [{char,L,C}|More];
tokens({integer,L,N}, More) -> [{integer,L,N}|More];
tokens({float,L,F}, More) -> [{float,L,F}|More];