Skip to content

Commit 35fae47

Browse files
josevalimJosé Valim
authored andcommitted
Add breakpoint support and user conveniences to IEx
1 parent cf8507b commit 35fae47

20 files changed

+1468
-223
lines changed

lib/elixir/lib/macro/env.ex

Lines changed: 5 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -44,8 +44,9 @@ defmodule Macro.Env do
4444
4545
* `export_vars` - a list keeping all variables to be exported in a
4646
construct (may be `nil`)
47-
* `match_vars` - a list of variables defined in a given match (is
48-
`nil` when not inside a match)
47+
* `match_vars` - controls how "new" variables are handled. Inside a
48+
match it is a list with all variables in a match. Outside of a match
49+
is either `:warn` or `:apply`
4950
* `prematch_vars` - a list of variables defined before a match (is
5051
`nil` when not inside a match)
5152
@@ -66,7 +67,7 @@ defmodule Macro.Env do
6667
@type local :: atom | nil
6768

6869
@opaque export_vars :: vars | nil
69-
@opaque match_vars :: vars | nil
70+
@opaque match_vars :: vars | :warn | :apply
7071
@opaque prematch_vars :: vars | nil
7172

7273
@type t :: %{__struct__: __MODULE__,
@@ -103,7 +104,7 @@ defmodule Macro.Env do
103104
vars: [],
104105
lexical_tracker: nil,
105106
export_vars: nil,
106-
match_vars: nil,
107+
match_vars: :warn,
107108
prematch_vars: nil}
108109
end
109110

lib/elixir/src/elixir.erl

Lines changed: 7 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -183,8 +183,14 @@ env_for_eval(Env, Opts) ->
183183
false -> nil
184184
end,
185185

186+
FA = case lists:keyfind(function, 1, Opts) of
187+
{function, {Function, Arity}} when is_atom(Function), is_integer(Arity) -> {Function, Arity};
188+
{function, nil} -> nil;
189+
false -> nil
190+
end,
191+
186192
Env#{
187-
file := File, module := Module,
193+
file := File, module := Module, function := FA,
188194
macros := Macros, functions := Functions,
189195
requires := Requires, aliases := Aliases, line := Line
190196
}.

lib/elixir/src/elixir_clauses.erl

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -9,13 +9,13 @@
99

1010
match(Fun, Expr, #{context := match} = E) ->
1111
Fun(Expr, E);
12-
match(Fun, Expr, #{context := Context, match_vars := nil, prematch_vars := nil, vars := Vars} = E) ->
12+
match(Fun, Expr, #{context := Context, match_vars := Match, prematch_vars := nil, vars := Vars} = E) ->
1313
{EExpr, EE} = Fun(Expr, E#{context := match, match_vars := [], prematch_vars := Vars}),
14-
{EExpr, EE#{context := Context, match_vars := nil, prematch_vars := nil}}.
14+
{EExpr, EE#{context := Context, match_vars := Match, prematch_vars := nil}}.
1515

16-
def({Meta, Args, Guards, Body}, E) ->
16+
def({Meta, Args, Guards, Body}, #{match_vars := Match} = E) ->
1717
{EArgs, EA} = elixir_expand:expand(Args, E#{context := match, match_vars := []}),
18-
{EGuards, EG} = guard(Guards, EA#{context := guard, match_vars := nil}),
18+
{EGuards, EG} = guard(Guards, EA#{context := guard, match_vars := Match}),
1919
{EBody, _} = elixir_expand:expand(Body, EG#{context := ?key(E, context)}),
2020
{Meta, EArgs, EGuards, EBody}.
2121

lib/elixir/src/elixir_env.erl

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -19,8 +19,8 @@ new() ->
1919
lexical_tracker => nil, %% holds the lexical tracker PID
2020
vars => [], %% a set of defined variables
2121
export_vars => nil, %% a set of variables to be exported in some constructs
22-
match_vars => nil, %% a set of variables defined in the current match
23-
prematch_vars => nil}. %% a set of variables defined before the current match
22+
prematch_vars => nil, %% a set of variables defined before the current match
23+
match_vars => warn}. %% handling of new variables
2424

2525
linify({Line, Env}) ->
2626
Env#{line := Line};

lib/elixir/src/elixir_erl_try.erl

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -28,14 +28,14 @@ each_clause({'catch', Meta, Raw, Expr}, S) ->
2828

2929
each_clause({rescue, Meta, [{in, _, [Left, Right]}], Expr}, S) ->
3030
{TempName, _, CS} = elixir_erl_var:build('_', S),
31-
TempVar = {TempName, Meta, nil},
31+
TempVar = {TempName, Meta, 'Elixir'},
3232
{Parts, Safe, FS} = rescue_guards(Meta, TempVar, Right, CS),
3333
Body = rescue_clause_body(Left, Expr, Safe, TempVar, Meta),
3434
build_rescue(Meta, Parts, Body, FS);
3535

3636
each_clause({rescue, Meta, [{VarName, _, Context} = Left], Expr}, S) when is_atom(VarName), is_atom(Context) ->
3737
{TempName, _, CS} = elixir_erl_var:build('_', S),
38-
TempVar = {TempName, Meta, nil},
38+
TempVar = {TempName, Meta, 'Elixir'},
3939
Body = rescue_clause_body(Left, Expr, false, TempVar, Meta),
4040
build_rescue(Meta, [{TempVar, []}], Body, CS).
4141

@@ -76,7 +76,7 @@ rescue_guards(Meta, Var, Aliases, S) ->
7676
[] -> {[], S};
7777
_ ->
7878
{VarName, _, CS} = elixir_erl_var:build('_', S),
79-
StructVar = {VarName, Meta, nil},
79+
StructVar = {VarName, Meta, 'Elixir'},
8080
Map = {'%{}', Meta, [{'__struct__', StructVar}, {'__exception__', true}]},
8181
Match = {'=', Meta, [Map, Var]},
8282
Guards = [{erl(Meta, '=='), Meta, [StructVar, Mod]} || Mod <- Elixir],

lib/elixir/src/elixir_expand.erl

Lines changed: 9 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -360,10 +360,15 @@ expand({Name, Meta, Kind} = Var, #{vars := Vars} = E) when is_atom(Name), is_ato
360360
{var, true} ->
361361
form_error(Meta, ?key(E, file), ?MODULE, {undefined_var, Name, Kind});
362362
_ ->
363-
Message =
364-
io_lib:format("variable \"~ts\" does not exist and is being expanded to \"~ts()\","
365-
" please use parentheses to remove the ambiguity or change the variable name", [Name, Name]),
366-
elixir_errors:warn(?line(Meta), ?key(E, file), Message),
363+
case ?key(E, match_vars) of
364+
warn ->
365+
Message =
366+
io_lib:format("variable \"~ts\" does not exist and is being expanded to \"~ts()\","
367+
" please use parentheses to remove the ambiguity or change the variable name", [Name, Name]),
368+
elixir_errors:warn(?line(Meta), ?key(E, file), Message);
369+
apply ->
370+
ok
371+
end,
367372
expand({Name, Meta, []}, E)
368373
end
369374
end;

0 commit comments

Comments
 (0)