aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/src/erl_internal.erl
diff options
context:
space:
mode:
authorBjörn Gustavsson <[email protected]>2016-08-16 14:19:59 +0200
committerBjörn Gustavsson <[email protected]>2016-09-01 15:16:02 +0200
commit04c67da5b455416c71fe9bc4c70fe61ceb7aad79 (patch)
treeb4d424d3c02e5d5ae42742760c1194f5814bf07f /lib/stdlib/src/erl_internal.erl
parentfeab3f976f265a45345b0a82ea656898db29603f (diff)
downloadotp-04c67da5b455416c71fe9bc4c70fe61ceb7aad79.tar.gz
otp-04c67da5b455416c71fe9bc4c70fe61ceb7aad79.tar.bz2
otp-04c67da5b455416c71fe9bc4c70fe61ceb7aad79.zip
erl_internal: Add add_predefined_functions/1
The sys_pre_expand module used to do a lot more (translate records and funs, for example), but now it does very little. Most of the code is an identify transformation of the abstract format. The identity transformation part of the code must be maintained and kept correct when new forms are added to the abstract format. That adds to the maintance burden. It also adds (slightly) to compilation times. Therefore, we want to eliminate sys_pre_expand, moving all of its (non-identity) transformations to better places. As a preliminary first step, move the code that adds the pre-defined functions (such as module_info/0) to a new function in erl_internal.
Diffstat (limited to 'lib/stdlib/src/erl_internal.erl')
-rw-r--r--lib/stdlib/src/erl_internal.erl67
1 files changed, 67 insertions, 0 deletions
diff --git a/lib/stdlib/src/erl_internal.erl b/lib/stdlib/src/erl_internal.erl
index 46059f42a5..5d6aa0ebe8 100644
--- a/lib/stdlib/src/erl_internal.erl
+++ b/lib/stdlib/src/erl_internal.erl
@@ -54,6 +54,8 @@
-export([is_type/2]).
+-export([add_predefined_functions/1]).
+
%%---------------------------------------------------------------------------
%% Erlang builtin functions allowed in guards.
@@ -569,3 +571,68 @@ is_type(term, 0) -> true;
is_type(timeout, 0) -> true;
is_type(tuple, 0) -> true;
is_type(_, _) -> false.
+
+%%%
+%%% Add and export the pre-defined functions:
+%%%
+%%% module_info/0
+%%% module_info/1
+%%% behaviour_info/1 (optional)
+%%%
+
+-spec add_predefined_functions(Forms) -> UpdatedForms when
+ Forms :: [erl_parse:abstract_form() | erl_parse:form_info()],
+ UpdatedForms :: [erl_parse:abstract_form() | erl_parse:form_info()].
+
+add_predefined_functions(Forms) ->
+ Forms ++ predefined_functions(Forms).
+
+predefined_functions(Forms) ->
+ Attrs = [{Name,Val} || {attribute,_,Name,Val} <- Forms],
+ {module,Mod} = lists:keyfind(module, 1, Attrs),
+ Callbacks = [Callback || {callback,Callback} <- Attrs],
+ OptionalCallbacks = get_optional_callbacks(Attrs),
+ Mpf1 = module_predef_func_beh_info(Callbacks, OptionalCallbacks),
+ Mpf2 = module_predef_funcs_mod_info(Mod),
+ Mpf = [erl_parse:new_anno(F) || F <- Mpf1++Mpf2],
+ Exp = [{F,A} || {function,_,F,A,_} <- Mpf],
+ [{attribute,0,export,Exp}|Mpf].
+
+get_optional_callbacks(Attrs) ->
+ L = [O || {optional_callbacks,O} <- Attrs, is_fa_list(O)],
+ lists:append(L).
+
+is_fa_list([{FuncName, Arity}|L])
+ when is_atom(FuncName), is_integer(Arity), Arity >= 0 ->
+ is_fa_list(L);
+is_fa_list([]) -> true;
+is_fa_list(_) -> false.
+
+module_predef_func_beh_info([], _) ->
+ [];
+module_predef_func_beh_info(Callbacks0, OptionalCallbacks) ->
+ Callbacks = [FA || {{_,_}=FA,_} <- Callbacks0],
+ List = make_list(Callbacks),
+ OptionalList = make_list(OptionalCallbacks),
+ [{function,0,behaviour_info,1,
+ [{clause,0,[{atom,0,callbacks}],[],[List]},
+ {clause,0,[{atom,0,optional_callbacks}],[],[OptionalList]}]}].
+
+make_list([]) -> {nil,0};
+make_list([{Name,Arity}|Rest]) ->
+ {cons,0,
+ {tuple,0,
+ [{atom,0,Name},
+ {integer,0,Arity}]},
+ make_list(Rest)}.
+
+module_predef_funcs_mod_info(Mod) ->
+ ModAtom = {atom,0,Mod},
+ [{function,0,module_info,0,
+ [{clause,0,[],[],
+ [{call,0,{remote,0,{atom,0,erlang},{atom,0,get_module_info}},
+ [ModAtom]}]}]},
+ {function,0,module_info,1,
+ [{clause,0,[{var,0,'X'}],[],
+ [{call,0,{remote,0,{atom,0,erlang},{atom,0,get_module_info}},
+ [ModAtom,{var,0,'X'}]}]}]}].