diff options
Diffstat (limited to 'lib/stdlib/src')
-rw-r--r-- | lib/stdlib/src/epp.erl | 123 |
1 files changed, 117 insertions, 6 deletions
diff --git a/lib/stdlib/src/epp.erl b/lib/stdlib/src/epp.erl index e823156af1..cc34d4bdd3 100644 --- a/lib/stdlib/src/epp.erl +++ b/lib/stdlib/src/epp.erl @@ -38,7 +38,7 @@ -type epp_handle() :: pid(). -type source_encoding() :: latin1 | utf8. --type ifdef() :: 'ifdef' | 'ifndef' | 'else'. +-type ifdef() :: 'ifdef' | 'ifndef' | 'if' | 'else'. -type name() :: atom(). -type argspec() :: 'none' %No arguments @@ -221,6 +221,8 @@ format_error({illegal_function,Macro}) -> io_lib:format("?~s can only be used within a function", [Macro]); format_error({illegal_function_usage,Macro}) -> io_lib:format("?~s must not begin a form", [Macro]); +format_error(elif_after_else) -> + "'elif' following 'else'"; format_error({'NYI',What}) -> io_lib:format("not yet implemented '~s'", [What]); format_error({error,Term}) -> @@ -1087,21 +1089,118 @@ scan_else(_Toks, Else, From, St) -> epp_reply(From, {error,{loc(Else),epp,{bad,'else'}}}), wait_req_scan(St). -%% scan_if(Tokens, EndifToken, From, EppState) +%% scan_if(Tokens, IfToken, From, EppState) %% Handle the conditional parsing of a file. -%% Report a badly formed if test and then treat as false macro. +scan_if([{'(',_}|_]=Toks, If, From, St) -> + try eval_if(Toks, St) of + true -> + scan_toks(From, St#epp{istk=['if'|St#epp.istk]}); + _ -> + skip_toks(From, St, ['if']) + catch + throw:Error0 -> + Error = case Error0 of + {_,erl_parse,_} -> + {error,Error0}; + _ -> + {error,{loc(If),epp,Error0}} + end, + epp_reply(From, Error), + wait_req_skip(St, ['if']) + end; scan_if(_Toks, If, From, St) -> - epp_reply(From, {error,{loc(If),epp,{'NYI','if'}}}), + epp_reply(From, {error,{loc(If),epp,{bad,'if'}}}), wait_req_skip(St, ['if']). +eval_if(Toks0, St) -> + Toks = expand_macros(Toks0, St), + Es1 = case erl_parse:parse_exprs(Toks) of + {ok,Es0} -> Es0; + {error,E} -> throw(E) + end, + Es = rewrite_expr(Es1, St), + assert_guard_expr(Es), + Bs = erl_eval:new_bindings(), + LocalFun = fun(_Name, _Args) -> + error(badarg) + end, + try erl_eval:exprs(Es, Bs, {value,LocalFun}) of + {value,Res,_} -> + Res + catch + _:_ -> + false + end. + +assert_guard_expr([E0]) -> + E = rewrite_expr(E0, none), + case erl_lint:is_guard_expr(E) of + false -> + throw({bad,'if'}); + true -> + ok + end; +assert_guard_expr(_) -> + throw({bad,'if'}). + +%% Dual-purpose rewriting function. When the second argument is +%% an #epp{} record, calls to defined(Symbol) will be evaluated. +%% When the second argument is 'none', legal calls to our built-in +%% functions are eliminated in order to turn the expression into +%% a legal guard expression. + +rewrite_expr({call,_,{atom,_,defined},[N0]}, #epp{macs=Macs}) -> + %% Evaluate defined(Symbol). + N = case N0 of + {var,_,N1} -> N1; + {atom,_,N1} -> N1; + _ -> throw({bad,'if'}) + end, + {atom,0,maps:is_key(N, Macs)}; +rewrite_expr({call,_,{atom,_,Name},As0}, none) -> + As = rewrite_expr(As0, none), + Arity = length(As), + case erl_internal:bif(Name, Arity) andalso + not erl_internal:guard_bif(Name, Arity) of + false -> + %% A guard BIF, an -if built-in, or an unknown function. + %% Eliminate the call so that erl_lint will not complain. + %% The call might fail later at evaluation time. + to_conses(As); + true -> + %% An auto-imported BIF (not guard BIF). Not allowed. + throw({bad,'if'}) + end; +rewrite_expr([H|T], St) -> + [rewrite_expr(H, St)|rewrite_expr(T, St)]; +rewrite_expr(Tuple, St) when is_tuple(Tuple) -> + list_to_tuple(rewrite_expr(tuple_to_list(Tuple), St)); +rewrite_expr(Other, _) -> + Other. + +to_conses([H|T]) -> + {cons,0,H,to_conses(T)}; +to_conses([]) -> + {nil,0}. + %% scan_elif(Tokens, EndifToken, From, EppState) %% Handle the conditional parsing of a file. %% Report a badly formed if test and then treat as false macro. scan_elif(_Toks, Elif, From, St) -> - epp_reply(From, {error,{loc(Elif),epp,{'NYI','elif'}}}), - wait_req_scan(St). + case St#epp.istk of + ['else'|Cis] -> + epp_reply(From, {error,{loc(Elif), + epp,{illegal,"unbalanced",'elif'}}}), + wait_req_skip(St#epp{istk=Cis}, ['else']); + [_I|Cis] -> + skip_toks(From, St#epp{istk=Cis}, ['elif']); + [] -> + epp_reply(From, {error,{loc(Elif),epp, + {illegal,"unbalanced",elif}}}), + wait_req_scan(St) + end. %% scan_endif(Tokens, EndifToken, From, EppState) %% If we are in an if body then exit it, else report an error. @@ -1160,6 +1259,8 @@ skip_toks(From, St, [I|Sis]) -> skip_toks(From, St#epp{location=Cl}, ['if',I|Sis]); {ok,[{'-',_Lh},{atom,_Le,'else'}=Else|_Toks],Cl}-> skip_else(Else, From, St#epp{location=Cl}, [I|Sis]); + {ok,[{'-',_Lh},{atom,_Le,'elif'}=Elif|Toks],Cl}-> + skip_elif(Toks, Elif, From, St#epp{location=Cl}, [I|Sis]); {ok,[{'-',_Lh},{atom,_Le,endif}|_Toks],Cl} -> skip_toks(From, St#epp{location=Cl}, Sis); {ok,_Toks,Cl} -> @@ -1190,11 +1291,21 @@ skip_toks(From, St, []) -> skip_else(Else, From, St, ['else'|Sis]) -> epp_reply(From, {error,{loc(Else),epp,{illegal,"repeated",'else'}}}), wait_req_skip(St, ['else'|Sis]); +skip_else(_Else, From, St, ['elif'|Sis]) -> + skip_toks(From, St, ['else'|Sis]); skip_else(_Else, From, St, [_I]) -> scan_toks(From, St#epp{istk=['else'|St#epp.istk]}); skip_else(_Else, From, St, Sis) -> skip_toks(From, St, Sis). +skip_elif(_Toks, Elif, From, St, ['else'|_]=Sis) -> + epp_reply(From, {error,{loc(Elif),epp,elif_after_else}}), + wait_req_skip(St, Sis); +skip_elif(Toks, Elif, From, St, [_I]) -> + scan_if(Toks, Elif, From, St); +skip_elif(_Toks, _Elif, From, St, Sis) -> + skip_toks(From, St, Sis). + %% macro_pars(Tokens, ArgStack) %% macro_expansion(Tokens, Anno) %% Extract the macro parameters and the expansion from a macro definition. |