diff --git a/lib/stdlib/src/edlin_expand.erl b/lib/stdlib/src/edlin_expand.erl index 43738966d76c..d4e27bcc7d6a 100644 --- a/lib/stdlib/src/edlin_expand.erl +++ b/lib/stdlib/src/edlin_expand.erl @@ -393,8 +393,8 @@ is_type(Type, Cs, String) -> catch _:_ -> %% Types not possible to deduce with erl_parse - % If string contains variables, erl_parse:parse_term will fail, but we - % consider them valid sooo.. lets replace them with the atom var + %% If string contains variables, erl_parse:parse_term will fail, but we + %% consider them valid sooo.. lets replace them with the atom var B = [(fun({var, Anno, _}) -> {atom, Anno, var}; (Token) -> Token end)(X) || X <- A], try {ok, Term2} = erl_parse:parse_term(B), @@ -730,41 +730,33 @@ expand_filepath(PathPrefix, Word) -> end. shell(Fun) when is_atom(Fun) -> - case lists:member(Fun, [E || {E,_}<-get_exports(shell)]) of + case shell:local_func(Fun) of true -> "shell"; - _ -> "user_defined" - end; -shell(Fun) -> - case erl_scan:string(Fun) of - {ok, [{var, _, _}], _} -> []; - {ok, [{atom, _, Fun1}], _} -> - shell(Fun1) + false -> "user_defined" end. -doc false. shell_default_or_bif(Fun) when is_atom(Fun) -> case lists:member(Fun, [E || {E,_}<-get_exports(shell_default)]) of true -> "shell_default"; - _ -> bif(Fun) + false -> bif(Fun) end; shell_default_or_bif(Fun) -> case erl_scan:string(Fun) of {ok, [{var, _, _}], _} -> []; - {ok, [{atom, _, Fun1}], _} -> - shell_default_or_bif(Fun1) + {ok, [{atom, _, Fun1}], _} -> shell_default_or_bif(Fun1) end. -doc false. bif(Fun) when is_atom(Fun) -> case lists:member(Fun, [E || {E,_}<-get_exports(erlang)]) of true -> "erlang"; - _ -> shell(Fun) + false -> shell(Fun) end; bif(Fun) -> case erl_scan:string(Fun) of {ok, [{var, _, _}], _} -> []; - {ok, [{atom, _, Fun1}], _} -> - bif(Fun1) + {ok, [{atom, _, Fun1}], _} -> bif(Fun1) end. expand_string(Bef0) -> diff --git a/lib/stdlib/src/erl_error.erl b/lib/stdlib/src/erl_error.erl index c5ae309ce12d..f8447e9f865a 100644 --- a/lib/stdlib/src/erl_error.erl +++ b/lib/stdlib/src/erl_error.erl @@ -536,10 +536,20 @@ location(L) -> sep(1, S) -> S; sep(_, S) -> [$\n | S]. +is_rec_init(F) when is_atom(F) -> + case atom_to_binary(F) of + <<"rec_init$^", _/binary>> -> true; + _ -> false + end; +is_rec_init(_) -> false. + origin(1, M, F, A) -> case is_op({M, F}, n_args(A)) of {yes, F} -> <<"in operator ">>; - no -> <<"in function ">> + no -> case is_rec_init(F) of + true -> <<"in record">>; + _ -> <<"in function ">> + end end; origin(_N, _M, _F, _A) -> <<"in call from">>. @@ -625,7 +635,10 @@ printable_list(_, As) -> io_lib:printable_list(As). mfa_to_string(M, F, A, Enc) -> - io_lib:fwrite(<<"~ts/~w">>, [mf_to_string({M, F}, A, Enc), A]). + case is_rec_init(F) of + true -> <<"default value">>; + false -> io_lib:fwrite(<<"~ts/~w">>, [mf_to_string({M, F}, A, Enc), A]) + end. mf_to_string({M, F}, A, Enc) -> case erl_internal:bif(M, F, A) of diff --git a/lib/stdlib/src/erl_expand_records.erl b/lib/stdlib/src/erl_expand_records.erl index 972aaada1a9b..8ad50098e12c 100644 --- a/lib/stdlib/src/erl_expand_records.erl +++ b/lib/stdlib/src/erl_expand_records.erl @@ -99,9 +99,9 @@ forms([F | Fs0], St0) -> {[F | Fs], St}; forms([], #exprec{new_forms=FsN}=St) -> {[{'function', Anno, - maps:get(Def,FsN), - 0, - [{'clause', Anno, [], [], [Def]}]} + maps:get(Def, FsN), + 0, + [{'clause', Anno, [], [], [Def]}]} || {_,Anno,_}=Def <- maps:keys(FsN)], St}; forms([], St) -> {[],St}. diff --git a/lib/stdlib/src/shell.erl b/lib/stdlib/src/shell.erl index 0d8afc403f5b..100deb0103de 100644 --- a/lib/stdlib/src/shell.erl +++ b/lib/stdlib/src/shell.erl @@ -1213,7 +1213,7 @@ expand_records(UsedRecords, E0, FT) -> [NE2]=reconstruct1(NE, [],0, []), ets:insert(FT, [begin {value, Fun, []} = erl_eval:expr({'fun', A, {clauses, F}}, []), {{function, {shell_default, FunName, 0}}, Fun} - end || {function,_,FunName,0,F}=_F1<-Forms, FunName=/=foo]), + end || {function,_,FunName,0,F}<-Forms, FunName=/=foo]), prep_rec(NE2). prep_rec({value,_CommandN,_V}=Value) -> @@ -1282,7 +1282,7 @@ help() -> %% non_builtin_local_func/3 (user_default/shell_default). %% fd, ft and td should not be exposed to the user -doc false. -local_func() -> [v,h,b,f,ff,fl,lf,lr,lt,rd,rf,rl,rp,rr,tf,save_module,history,results,catch_exception]. +local_func() -> [v,h,b,f,fd,ff,fl,lf,lr,lt,rd,rf,rl,rp,rr,tf,save_module,history,results,catch_exception]. -doc false. local_func(Func) -> lists:member(Func, local_func()). @@ -1851,20 +1851,9 @@ inc_paths(Opts) -> [P || {i,P} <- Opts, is_list(P)]. record_attrs(Forms, Mod) -> - Exports = case erlang:module_loaded(Mod) of - true -> - Mod:module_info(exports); - false -> - case beam_lib:chunks(code:which(Mod), [exports]) of - {ok, {Mod, [{exports,E}]}} -> - E; - _ -> - [] - end - end, %% Add module Mod to exported local functions, add shell_default otherwise [begin [X] = reconstruct1([A], [], 0, - [{module,Mod},{exports,Exports}]), + [{module,Mod},{exports,edlin_expand:get_exports(Mod)}]), X end || A = {attribute,_,record,_D} <- Forms]. %%% End of reading record information from file(s) diff --git a/lib/stdlib/test/shell_SUITE.erl b/lib/stdlib/test/shell_SUITE.erl index 9b50f8cee370..3780fd53f765 100644 --- a/lib/stdlib/test/shell_SUITE.erl +++ b/lib/stdlib/test/shell_SUITE.erl @@ -189,11 +189,11 @@ comm_err(<<"ugly().">>), comm_err(<<"1 - 2.">>), %% Make sure we test all local shell functions in a restricted shell. LocalFuncs = shell:local_func(), -[] = lists:subtract(LocalFuncs, [v,h,b,f,fl,ff,lf,lr,lt,rd,rf,rl,rp,rr,tf,save_module,history,results,catch_exception]), +[] = lists:subtract(LocalFuncs, [v,h,b,f,fd,fl,ff,lf,lr,lt,rd,rf,rl,rp,rr,tf,save_module,history,results,catch_exception]), LocalFuncs2 = [ <<"A = 1.\nv(1).">>, <<"h().">>, <<"b().">>, <<"f().">>, <<"f(A).">>, - <<"fl()">>, <<"ff()">>, <<"ff(my_func,1)">>, <<"lf()">>, <<"lr()">>, <<"lt()">>, + <<"fl()">>, <<"fd()">>, <<"ff()">>, <<"ff(my_func,1)">>, <<"lf()">>, <<"lr()">>, <<"lt()">>, <<"rd(foo,{bar}).">>, <<"rf().">>, <<"rf(foo).">>, <<"rl().">>, <<"rl(foo).">>, <<"rp([hej]).">>, <<"rr(shell).">>, <<"rr(shell, shell_state).">>, <<"rr(shell,shell_state,[]).">>, <<"tf()">>, <<"tf(hej)">>, <<"save_module(\"src/my_module.erl\")">>, <<"history(20).">>, <<"results(20).">>, <<"catch_exception(0).">>], @@ -520,6 +520,19 @@ records(Config) when is_list(Config) -> ok = file:write_file(Test, Contents), {ok, test} = compile:file(Test, [{outdir, BeamDir}]), + ErrorMod = """ + -module(error_record_init). + -export([t/0]). + -record(r_error, {a=case 1 of X -> X=2 end}). + t() -> + #r_error{}. + """, + ErrorModFile = filename:join(proplists:get_value(priv_dir, Config), "error_record_init.erl"), + ok = file:write_file(ErrorModFile, ErrorMod), + {ok, error_record_init} = compile:file(ErrorModFile, [outdir, BeamDir]), + "** exception error: no match of right hand side value 2\n in record default value (" ++ Rest1 = t("error_record_init:t()."), + true = (nomatch =/= string:find(Rest1, "error_record_init.erl, line 5).\n", trailing)), + RR5 = "rr(\"" ++ Test ++ "\", '_', {d,test1}), rl([test1,test2]).", A1 = erl_anno:new(1), [{attribute,A1,record,{test1,_}},ok] = scan(RR5),