Skip to content

Commit 174f031

Browse files
author
José Valim
committed
Eval should take into account other contexts
1 parent f1e2fcf commit 174f031

File tree

5 files changed

+64
-56
lines changed

5 files changed

+64
-56
lines changed

lib/elixir/lib/code.ex

Lines changed: 11 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -56,7 +56,7 @@ defmodule Code do
5656
end
5757

5858
@doc """
59-
Evaluates the contents given by `string`. The second argument is
59+
Evaluates the contents given by `string`. The second argument is
6060
a keyword list of variable bindings, followed by a keyword list of
6161
environment options. Those options can be:
6262
@@ -83,9 +83,13 @@ defmodule Code do
8383
etc.
8484
8585
Returns a tuple of the form `{ value, binding }`,
86-
where `value` is the the value returned from evaluating `string`; `binding`
87-
is a keyword list with the value of all variable bindings after evaluating
88-
`string`. If an error occurs while evaluating `string` an exception will be raised.
86+
where `value` is the the value returned from evaluating `string`.
87+
If an error occurs while evaluating `string` an exception will be raised.
88+
89+
`binding` is a keyword list with the value of all variable bindings
90+
after evaluating `string`. The binding key is usually an atom, but it
91+
may be a tuple for variables defined in another contexts that are not
92+
the main one.
8993
9094
## Examples
9195
@@ -95,7 +99,7 @@ defmodule Code do
9599
iex> Code.eval_string("c = a + b", [a: 1, b: 2], __ENV__)
96100
{3, [a: 1, b: 2, c: 3]}
97101
98-
iex> Code.eval_string("a = a + b", [a: 1, b: 2])
102+
iex> Code.eval_string("a = a + b", [a: 1, b: 2])
99103
{3, [a: 3, b: 2]}
100104
101105
For convenience, you can pass `__ENV__` as the `opts` argument and
@@ -362,7 +366,7 @@ defmodule Code do
362366
modules need to be loaded upfront or explicitly.
363367
364368
Therefore, this function is used to check if a module is loaded
365-
before using it and allows one to react accordingly. For example, the `URI`
369+
before using it and allows one to react accordingly. For example, the `URI`
366370
module uses this function to check if a specific parser exists for a given
367371
URI scheme.
368372
@@ -397,7 +401,7 @@ defmodule Code do
397401
@doc """
398402
Ensures the given module is compiled and loaded. If the module
399403
is already loaded, it works as no-op. If the module was not
400-
loaded yet, it checks if it needs to be compiled first and
404+
loaded yet, it checks if it needs to be compiled first and
401405
then tries to load it.
402406
403407
If it succeeds loading the module, it returns

lib/elixir/src/elixir.erl

Lines changed: 11 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -2,9 +2,8 @@
22
-behaviour(application).
33
-export([main/1, start_cli/0,
44
scope_for_eval/1, scope_for_eval/2,
5-
eval/2, eval/3, eval/4,
6-
eval_quoted/2, eval_quoted/3, eval_quoted/4,
7-
eval_forms/3, translate_forms/3]).
5+
eval/2, eval/3, eval/4, eval_forms/3,
6+
eval_quoted/2, eval_quoted/3, eval_quoted/4]).
87
-include("elixir.hrl").
98

109
%% Top level types
@@ -124,17 +123,16 @@ eval_quoted(Tree, Binding, Line, #elixir_scope{} = S) when is_integer(Line) ->
124123
%% Handle forms evaluation internally, it is an
125124
%% internal API not meant for external usage.
126125

127-
translate_forms(Tree, Binding, Opts) when is_list(Opts) ->
128-
translate_forms(Tree, Binding, scope_for_eval(Opts));
129-
130-
translate_forms(Tree, Binding, #elixir_scope{} = Scope) ->
131-
elixir_translator:translate(Tree, elixir_scope:vars_from_binding(Scope, Binding)).
126+
eval_forms(Tree, Binding, Opts) when is_list(Opts) ->
127+
eval_forms(Tree, Binding, scope_for_eval(Opts));
132128

133129
eval_forms(Tree, Binding, Scope) ->
134-
{ ParseTree, NewScope } = translate_forms(Tree, Binding, Scope),
135-
case ParseTree of
136-
[] -> { nil, Binding, NewScope };
130+
{ ParsedBinding, ParsedScope } = elixir_scope:load_binding(Binding, Scope, nil),
131+
{ Exprs, NewScope } = elixir_translator:translate(Tree, ParsedScope),
132+
case Exprs of
133+
[] ->
134+
{ nil, Binding, NewScope };
137135
_ ->
138-
{value, Value, NewBinding} = erl_eval:exprs(ParseTree, elixir_scope:binding_for_eval(Binding, nil)),
139-
{Value, elixir_scope:binding_from_vars(NewScope, NewBinding), NewScope }
136+
{ value, Value, NewBinding } = erl_eval:exprs(Exprs, ParsedBinding),
137+
{ Value, elixir_scope:dump_binding(NewBinding, NewScope), NewScope }
140138
end.

lib/elixir/src/elixir_module.erl

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,7 @@
88
-define(persisted_attr, '__persisted_attributes').
99

1010
eval_quoted(Module, Quoted, RawBinding, Opts) ->
11-
Binding = elixir_scope:binding_for_eval(RawBinding, Module),
11+
Binding = orddict:store('_@MODULE', Module, RawBinding),
1212
Scope = scope_for_eval(Module, Opts),
1313

1414
elixir_def:reset_last(Module),
@@ -385,8 +385,7 @@ else_clause() ->
385385
% HELPERS
386386

387387
eval_callbacks(Line, Module, Name, Args, RawS) ->
388-
Binding = elixir_scope:binding_for_eval([], Module),
389-
S = elixir_scope:vars_from_binding(RawS, Binding),
388+
{ Binding, S } = elixir_scope:load_binding([], RawS, Module),
390389
Callbacks = lists:reverse(ets:lookup_element(data_table(Module), Name, 2)),
391390
Meta = [{line,Line},{require,false}],
392391

lib/elixir/src/elixir_scope.erl

Lines changed: 36 additions & 33 deletions
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,7 @@
55
serialize/1, deserialize/1,
66
serialize_with_vars/2, deserialize_with_vars/2,
77
to_erl_env/1, to_ex_env/1,
8-
vars_from_binding/2, binding_for_eval/2, binding_from_vars/2,
8+
load_binding/3, dump_binding/2,
99
umergev/2, umergec/2, umergea/2, merge_clause_vars/2
1010
]).
1111
-include("elixir.hrl").
@@ -207,37 +207,40 @@ var_number([], Acc) -> list_to_integer(lists:reverse(Acc)).
207207

208208
%% Setup the vars in scope from binding
209209

210-
vars_from_binding(Scope, Binding) ->
211-
Scope#elixir_scope{
212-
vars=binding_dict(Binding),
210+
load_binding(Binding, Scope, Module) ->
211+
{ NewBinding, NewVars, NewCounter } = load_binding(Binding, [], [], 0, Module),
212+
{ NewBinding, Scope#elixir_scope{
213+
vars=NewVars,
213214
temp_vars=[],
214215
clause_vars=nil,
215-
counter=[]
216-
}.
217-
218-
binding_dict(List) -> binding_dict(List, orddict:new()).
219-
binding_dict([{{H,Kind},_}|T], Dict) -> binding_dict(T, orddict:store({ H, Kind }, H, Dict));
220-
binding_dict([{H,_}|T], Dict) -> binding_dict(T, orddict:store({ H, nil }, H, Dict));
221-
binding_dict([], Dict) -> Dict.
222-
223-
binding_for_eval(Binding, Module) ->
224-
Keyword = orddict:from_list(Binding),
225-
case orddict:find('_@MODULE', Keyword) of
226-
{ ok, _ } -> Keyword;
227-
_ -> orddict:store('_@MODULE', Module, Keyword)
228-
end.
229-
230-
binding_from_vars(#elixir_scope{vars=Vars}, Binding) ->
231-
binding_from_vars(Binding, [], Binding, Vars).
232-
233-
binding_from_vars([{Var,_}|T], Acc, Binding, Vars) ->
234-
case lists:member($@, atom_to_list(Var)) of
235-
true ->
236-
binding_from_vars(T, Acc, Binding, Vars);
237-
false ->
238-
RealName = orddict:fetch({ Var, nil }, Vars),
239-
RealValue = proplists:get_value(RealName, Binding, nil),
240-
binding_from_vars(T, [{Var, RealValue}|Acc], Binding, Vars)
241-
end;
242-
243-
binding_from_vars([], Acc, _Binding, _Vars) -> lists:reverse(Acc).
216+
counter=[{'',NewCounter}]
217+
} }.
218+
219+
load_binding([{'_@MODULE',Value}|T], Binding, Vars, Counter, _Module) ->
220+
load_binding(T, Binding, Vars, Counter, Value);
221+
load_binding([{Key,Value}|T], Binding, Vars, Counter, Module) ->
222+
Actual = case Key of
223+
{ _Name, _Kind } -> Key;
224+
Name when is_atom(Name) -> { Name, nil }
225+
end,
226+
InternalName = ?atom_concat(["_@", Counter]),
227+
load_binding(T,
228+
[{InternalName,Value}|Binding],
229+
orddict:store(Actual, InternalName, Vars),
230+
Counter + 1, Module);
231+
load_binding([], Binding, Vars, Counter, Module) ->
232+
{ lists:reverse([{'_@MODULE',Module}|Binding]), Vars, Counter }.
233+
234+
dump_binding(Binding, #elixir_scope{vars=Vars}) ->
235+
dump_binding(Vars, Binding, []).
236+
237+
dump_binding([{{Var,Kind}=Key,InternalName}|T], Binding, Acc) when is_atom(Kind) ->
238+
Actual = case Kind of
239+
nil -> Var;
240+
_ -> Key
241+
end,
242+
Value = proplists:get_value(InternalName, Binding, nil),
243+
dump_binding(T, Binding, orddict:store(Actual, Value, Acc));
244+
dump_binding([_|T], Binding, Acc) ->
245+
dump_binding(T, Binding, Acc);
246+
dump_binding([], _Binding, Acc) -> Acc.

lib/elixir/test/elixir/code_test.exs

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -19,6 +19,10 @@ defmodule CodeTest do
1919
assert { 3, _ } = Code.eval_string("a + b", [a: 1, b: 2], __ENV__.location)
2020
end
2121

22+
test :eval_string_with_other_context do
23+
assert Code.eval_string("var!(a, Sample) = 1") == { 1, [{{:a,Sample},1}] }
24+
end
25+
2226
test :eval_with_unnamed_scopes do
2327
assert { RuntimeError[], [a: RuntimeError[]] } =
2428
Code.eval_string("a = (try do (raise \"hello\") rescue e -> e end)")

0 commit comments

Comments
 (0)