aboutsummaryrefslogtreecommitdiffstats
path: root/lib/stdlib/src/qlc_pt.erl
diff options
context:
space:
mode:
Diffstat (limited to 'lib/stdlib/src/qlc_pt.erl')
-rw-r--r--lib/stdlib/src/qlc_pt.erl59
1 files changed, 40 insertions, 19 deletions
diff --git a/lib/stdlib/src/qlc_pt.erl b/lib/stdlib/src/qlc_pt.erl
index 0db63b81f4..4a39f8ae9d 100644
--- a/lib/stdlib/src/qlc_pt.erl
+++ b/lib/stdlib/src/qlc_pt.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
-%% Copyright Ericsson AB 2004-2016. All Rights Reserved.
+%% Copyright Ericsson AB 2004-2017. All Rights Reserved.
%%
%% Licensed under the Apache License, Version 2.0 (the "License");
%% you may not use this file except in compliance with the License.
@@ -41,6 +41,7 @@
}).
-record(state, {imp,
+ overridden,
maxargs,
records,
xwarnings = [],
@@ -184,7 +185,9 @@ initiate(Forms0, Imported) ->
exclude_integers_from_unique_line_numbers(Forms0, NodeInfo),
?DEBUG("node info0 ~p~n",
[lists:sort(ets:tab2list(NodeInfo))]),
+ IsOverridden = set_up_overridden(Forms0),
State0 = #state{imp = Imported,
+ overridden = IsOverridden,
maxargs = ?EVAL_MAX_NUM_OF_ARGS,
records = record_attributes(Forms0),
node_info = NodeInfo},
@@ -436,7 +439,7 @@ compile_forms(Forms0, Options) ->
(_) -> false
end,
Forms = ([F || F <- Forms0, not Exclude(element(1, F))]
- ++ [{eof,anno0()}]),
+ ++ [{eof,0}]),
try
case compile:noenv_forms(Forms, compile_options(Options)) of
{ok, _ModName, Ws0} ->
@@ -1519,36 +1522,35 @@ filter_info(FilterData, AllIVs, Dependencies, State) ->
%% to be placed after further generators (the docs states otherwise, but
%% this seems to be common practice).
filter_list(FilterData, Dependencies, State) ->
- RDs = State#state.records,
- sel_gf(FilterData, 1, Dependencies, RDs, [], []).
+ sel_gf(FilterData, 1, Dependencies, State, [], []).
sel_gf([], _N, _Deps, _RDs, _Gens, _Gens1) ->
[];
-sel_gf([{#qid{no = N}=Id,{fil,F}}=Fil | FData], N, Deps, RDs, Gens, Gens1) ->
- case erl_lint:is_guard_test(F, RDs) of
+sel_gf([{#qid{no = N}=Id,{fil,F}}=Fil | FData], N, Deps, State, Gens, Gens1) ->
+ case is_guard_test(F, State) of
true ->
{Id,GIds} = lists:keyfind(Id, 1, Deps),
case length(GIds) =< 1 of
true ->
case generators_in_scope(GIds, Gens1) of
true ->
- [Fil|sel_gf(FData, N+1, Deps, RDs, Gens, Gens1)];
+ [Fil|sel_gf(FData, N+1, Deps, State, Gens, Gens1)];
false ->
- sel_gf(FData, N + 1, Deps, RDs, [], [])
+ sel_gf(FData, N + 1, Deps, State, [], [])
end;
false ->
case generators_in_scope(GIds, Gens) of
true ->
- [Fil | sel_gf(FData, N + 1, Deps, RDs, Gens, [])];
+ [Fil | sel_gf(FData, N + 1, Deps, State, Gens, [])];
false ->
- sel_gf(FData, N + 1, Deps, RDs, [], [])
+ sel_gf(FData, N + 1, Deps, State, [], [])
end
end;
false ->
- sel_gf(FData, N + 1, Deps, RDs, [], [])
+ sel_gf(FData, N + 1, Deps, State, [], [])
end;
-sel_gf(FData, N, Deps, RDs, Gens, Gens1) ->
- sel_gf(FData, N + 1, Deps, RDs, [N | Gens], [N | Gens1]).
+sel_gf(FData, N, Deps, State, Gens, Gens1) ->
+ sel_gf(FData, N + 1, Deps, State, [N | Gens], [N | Gens1]).
generators_in_scope(GenIds, GenNumbers) ->
lists:all(fun(#qid{no=N}) -> lists:member(N, GenNumbers) end, GenIds).
@@ -1870,7 +1872,8 @@ prep_expr(E, F, S, BF, Imported) ->
unify_column(Frame, Var, Col, BindFun, Imported) ->
A = anno0(),
- Call = {call,A,{atom,A,element},[{integer,A,Col}, {var,A,Var}]},
+ Call = {call,A,{remote,A,{atom,A,erlang},{atom,A,element}},
+ [{integer,A,Col}, {var,A,Var}]},
element_calls(Call, Frame, BindFun, Imported).
%% cons_tuple is used for representing {V1, ..., Vi | TupleTail}.
@@ -1880,6 +1883,8 @@ unify_column(Frame, Var, Col, BindFun, Imported) ->
%% about the size of the tuple is known.
element_calls({call,_,{remote,_,{atom,_,erlang},{atom,_,element}},
[{integer,_,I},Term0]}, F0, BF, Imported) when I > 0 ->
+ %% Note: erl_expand_records ensures that all calls to element/2
+ %% have an explicit "erlang:" prefix.
TupleTail = unique_var(),
VarsL = [unique_var() || _ <- lists:seq(1, I)],
Vars = VarsL ++ TupleTail,
@@ -1887,10 +1892,6 @@ element_calls({call,_,{remote,_,{atom,_,erlang},{atom,_,element}},
VarI = lists:nth(I, VarsL),
{Term, F} = element_calls(Term0, F0, BF, Imported),
{VarI, unify('=:=', Tuple, Term, F, BF, Imported)};
-element_calls({call,L1,{atom,_,element}=E,As}, F0, BF, Imported) ->
- %% erl_expand_records should add "erlang:"...
- element_calls({call,L1,{remote,L1,{atom,L1,erlang},E}, As}, F0, BF,
- Imported);
element_calls(T, F0, BF, Imported) when is_tuple(T) ->
{L, F} = element_calls(tuple_to_list(T), F0, BF, Imported),
{list_to_tuple(L), F};
@@ -2484,7 +2485,7 @@ filter(E, L, QIVs, S, RL, Fun, Go, GoI, IVs, State) ->
%% This is the "guard semantics" used in ordinary list
%% comprehension: if a filter looks like a guard test, it returns
%% 'false' rather than fails.
- Body = case erl_lint:is_guard_test(E, State#state.records) of
+ Body = case is_guard_test(E, State) of
true ->
CT = {clause,L,[],[[E]],[{call,L,?V(Fun),NAsT}]},
CF = {clause,L,[],[[?A(true)]],[{call,L,?V(Fun),NAsF}]},
@@ -2888,6 +2889,26 @@ family_list(L) ->
family(L) ->
sofs:relation_to_family(sofs:relation(L)).
+is_guard_test(E, #state{records = RDs, overridden = IsOverridden}) ->
+ erl_lint:is_guard_test(E, RDs, IsOverridden).
+
+%% In code that has been run through erl_expand_records, a guard
+%% test will never contain calls without an explicit module
+%% prefix. Unfortunately, this module runs *some* of the code
+%% through erl_expand_records, but not all of it.
+%%
+%% Therefore, we must set up our own list of local and imported functions
+%% that will override a BIF with the same name.
+
+set_up_overridden(Forms) ->
+ Locals = [{Name,Arity} || {function,_,Name,Arity,_} <- Forms],
+ Imports0 = [Fs || {attribute,_,import,Fs} <- Forms],
+ Imports1 = lists:flatten(Imports0),
+ Imports2 = [Fs || {_,Fs} <- Imports1],
+ Imports = lists:flatten(Imports2),
+ Overridden = gb_sets:from_list(Imports ++ Locals),
+ fun(FA) -> gb_sets:is_element(FA, Overridden) end.
+
-ifdef(debug).
display_forms(Forms) ->
io:format("Forms ***~n"),