Skip to content

Commit 2a69400

Browse files
author
José Valim
committed
Move environment cache to locals tracker, which is per module
1 parent 2a19411 commit 2a69400

File tree

8 files changed

+99
-100
lines changed

8 files changed

+99
-100
lines changed

lib/elixir/lib/kernel.ex

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -2989,7 +2989,7 @@ defmodule Kernel do
29892989

29902990
# Do not check clauses if any expression was unquoted
29912991
check_clauses = not(ue or uc)
2992-
pos = :elixir_env.cache(env)
2992+
pos = :elixir_locals.cache_env(env)
29932993

29942994
quote do
29952995
:elixir_def.store_definition(unquote(line), unquote(kind), unquote(check_clauses),

lib/elixir/lib/kernel/lexical_tracker.ex

Lines changed: 24 additions & 49 deletions
Original file line numberDiff line numberDiff line change
@@ -83,16 +83,6 @@ defmodule Kernel.LexicalTracker do
8383
unused(pid, @alias)
8484
end
8585

86-
@doc false
87-
def cache(pid, env) do
88-
:gen_server.call(pid, { :cache, env }, @timeout)
89-
end
90-
91-
@doc false
92-
def get_cached(pid, ref) do
93-
:gen_server.call(pid, { :get_cached, ref }, @timeout)
94-
end
95-
9686
defp unused(pid, pos) do
9787
ets = :gen_server.call(pid, :ets, @timeout)
9888
:ets.foldl(fn
@@ -107,75 +97,60 @@ defmodule Kernel.LexicalTracker do
10797

10898

10999
def init([]) do
110-
{ :ok, { :ets.new(:lexical, [:protected]), [] } }
111-
end
112-
113-
def handle_call({ :cache, env }, _from, { d, cache }) do
114-
case cache do
115-
[{i,^env}|_] ->
116-
{ :reply, i, { d, cache } }
117-
t ->
118-
i = length(t)
119-
{ :reply, i, { d, [{i,env}|t] } }
120-
end
121-
end
122-
123-
def handle_call({ :get_cached, ref }, _from, { _, cache } = state) do
124-
{ ^ref, env } = :lists.keyfind(ref, 1, cache)
125-
{ :reply, env, state }
100+
{ :ok, :ets.new(:lexical, [:protected]) }
126101
end
127102

128-
def handle_call(:ets, _from, { d, _ } = state) do
129-
{ :reply, d, state }
103+
def handle_call(:ets, _from, d) do
104+
{ :reply, d, d }
130105
end
131106

132-
def handle_call(_request, _from, state) do
133-
{ :noreply, state }
107+
def handle_call(request, _from, d) do
108+
{ :stop, { :bad_call, request }, d }
134109
end
135110

136-
def handle_cast({ :remote_dispatch, module }, { d, _ } = state) do
111+
def handle_cast({ :remote_dispatch, module }, d) do
137112
add_module(d, module)
138-
{ :noreply, state }
113+
{ :noreply, d }
139114
end
140115

141-
def handle_cast({ :import_dispatch, module }, { d, _ } = state) do
116+
def handle_cast({ :import_dispatch, module }, d) do
142117
add_dispatch(d, module, @import)
143-
{ :noreply, state }
118+
{ :noreply, d }
144119
end
145120

146-
def handle_cast({ :alias_dispatch, module }, { d, _ } = state) do
121+
def handle_cast({ :alias_dispatch, module }, d) do
147122
add_dispatch(d, module, @alias)
148-
{ :noreply, state }
123+
{ :noreply, d }
149124
end
150125

151-
def handle_cast({ :add_import, module, line, warn }, { d, _ } = state) do
126+
def handle_cast({ :add_import, module, line, warn }, d) do
152127
add_directive(d, module, line, warn, @import)
153-
{ :noreply, state }
128+
{ :noreply, d }
154129
end
155130

156-
def handle_cast({ :add_alias, module, line, warn }, { d, _ } = state) do
131+
def handle_cast({ :add_alias, module, line, warn }, d) do
157132
add_directive(d, module, line, warn, @alias)
158-
{ :noreply, state }
133+
{ :noreply, d }
159134
end
160135

161-
def handle_cast(:stop, state) do
162-
{ :stop, :normal, state }
136+
def handle_cast(:stop, d) do
137+
{ :stop, :normal, d }
163138
end
164139

165-
def handle_cast(_msg, state) do
166-
{ :noreply, state }
140+
def handle_cast(msg, d) do
141+
{ :stop, { :bad_cast, msg }, d }
167142
end
168143

169-
def handle_info(_msg, state) do
170-
{ :noreply, state }
144+
def handle_info(_msg, d) do
145+
{ :noreply, d }
171146
end
172147

173-
def terminate(_reason, _state) do
148+
def terminate(_reason, _d) do
174149
:ok
175150
end
176151

177-
def code_change(_old, state, _extra) do
178-
{ :ok, state }
152+
def code_change(_old, d, _extra) do
153+
{ :ok, d }
179154
end
180155

181156
# Callbacks helpers

lib/elixir/lib/module/locals_tracker.ex

Lines changed: 51 additions & 26 deletions
Original file line numberDiff line numberDiff line change
@@ -186,6 +186,16 @@ defmodule Module.LocalsTracker do
186186
end
187187
end
188188

189+
@doc false
190+
def cache_env(pid, env) do
191+
:gen_server.call(pid, { :cache_env, env }, @timeout)
192+
end
193+
194+
@doc false
195+
def get_cached_env(pid, ref) do
196+
:gen_server.call(pid, { :get_cached_env, ref }, @timeout)
197+
end
198+
189199
# Stops the gen server
190200
@doc false
191201
def stop(pid) do
@@ -197,71 +207,86 @@ defmodule Module.LocalsTracker do
197207
def init([]) do
198208
d = :digraph.new([:protected])
199209
:digraph.add_vertex(d, :local)
200-
{ :ok, d }
210+
{ :ok, { d, [] } }
211+
end
212+
213+
def handle_call({ :cache_env, env }, _from, { d, cache }) do
214+
case cache do
215+
[{i,^env}|_] ->
216+
{ :reply, i, { d, cache } }
217+
t ->
218+
i = length(t)
219+
{ :reply, i, { d, [{i,env}|t] } }
220+
end
221+
end
222+
223+
def handle_call({ :get_cached_env, ref }, _from, { _, cache } = state) do
224+
{ ^ref, env } = :lists.keyfind(ref, 1, cache)
225+
{ :reply, env, state }
201226
end
202227

203-
def handle_call({ :yank, local }, _from, d) do
228+
def handle_call({ :yank, local }, _from, { d, _ } = state) do
204229
in_vertices = :digraph.in_neighbours(d, local)
205230
out_vertices = :digraph.out_neighbours(d, local)
206231
:digraph.del_vertex(d, local)
207-
{ :reply, { in_vertices, out_vertices }, d }
232+
{ :reply, { in_vertices, out_vertices }, state }
208233
end
209234

210-
def handle_call(:digraph, _from, d) do
211-
{ :reply, d, d }
235+
def handle_call(:digraph, _from, { d, _ } = state) do
236+
{ :reply, d, state }
212237
end
213238

214-
def handle_call(_request, _from, d) do
215-
{ :noreply, d }
239+
def handle_call(request, _from, state) do
240+
{ :stop, { :bad_call, request }, state }
216241
end
217242

218-
def handle_info(_msg, d) do
219-
{ :noreply, d }
243+
def handle_info(_msg, state) do
244+
{ :noreply, state }
220245
end
221246

222-
def handle_cast({ :add_local, from, to }, d) do
247+
def handle_cast({ :add_local, from, to }, { d, _ } = state) do
223248
handle_add_local(d, from, to)
224-
{ :noreply, d }
249+
{ :noreply, state }
225250
end
226251

227-
def handle_cast({ :add_import, function, module, { name, arity } }, d) do
252+
def handle_cast({ :add_import, function, module, { name, arity } }, { d, _ } = state) do
228253
handle_import(d, function, module, name, arity)
229-
{ :noreply, d }
254+
{ :noreply, state }
230255
end
231256

232-
def handle_cast({ :add_definition, kind, tuple }, d) do
257+
def handle_cast({ :add_definition, kind, tuple }, { d, _ } = state) do
233258
handle_add_definition(d, kind, tuple)
234-
{ :noreply, d }
259+
{ :noreply, state }
235260
end
236261

237-
def handle_cast({ :add_defaults, kind, { name, arity }, defaults }, d) do
262+
def handle_cast({ :add_defaults, kind, { name, arity }, defaults }, { d, _ } = state) do
238263
lc i inlist :lists.seq(arity - defaults, arity - 1) do
239264
handle_add_definition(d, kind, { name, i })
240265
handle_add_local(d, { name, i }, { name, i + 1 })
241266
end
242-
{ :noreply, d }
267+
{ :noreply, state }
243268
end
244269

245-
def handle_cast({ :reattach, tuple, { in_neigh, out_neigh } }, d) do
270+
def handle_cast({ :reattach, tuple, { in_neigh, out_neigh } }, { d, _ } = state) do
246271
lc from inlist in_neigh, do: replace_edge(d, from, tuple)
247272
lc to inlist out_neigh, do: replace_edge(d, tuple, to)
248-
{ :noreply, d }
273+
{ :noreply, state }
249274
end
250275

251-
def handle_cast(:stop, d) do
252-
{ :stop, :normal, d }
276+
def handle_cast(:stop, state) do
277+
{ :stop, :normal, state }
253278
end
254279

255-
def handle_cast(_msg, d) do
256-
{ :noreply, d }
280+
def handle_cast(msg, state) do
281+
{ :stop, { :bad_cast, msg }, state }
257282
end
258283

259-
def terminate(_reason, _d) do
284+
def terminate(_reason, _state) do
260285
:ok
261286
end
262287

263-
def code_change(_old, d, _extra) do
264-
{ :ok, d }
288+
def code_change(_old, state, _extra) do
289+
{ :ok, state }
265290
end
266291

267292
defp handle_import(d, function, module, name, arity) do

lib/elixir/src/elixir_bootstrap.erl

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -38,7 +38,7 @@
3838
define({Line,E}, Kind, Call, Expr) ->
3939
{ EscapedCall, UC } = elixir_quote:escape(Call, true),
4040
{ EscapedExpr, UE } = elixir_quote:escape(Expr, true),
41-
Args = [Line, Kind, not(UC or UE), EscapedCall, EscapedExpr, elixir_env:cache(E)],
41+
Args = [Line, Kind, not(UC or UE), EscapedCall, EscapedExpr, elixir_locals:cache_env(E)],
4242
{ { '.', [], [elixir_def, store_definition] }, [], Args }.
4343

4444
unless_loaded(Fun, Args, Callback) ->

lib/elixir/src/elixir_compiler.erl

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -200,6 +200,7 @@ core_main() ->
200200
<<"lib/elixir/lib/macro/env.ex">>,
201201
<<"lib/elixir/lib/exception.ex">>,
202202
<<"lib/elixir/lib/code.ex">>,
203+
<<"lib/elixir/lib/module/locals_tracker.ex">>,
203204
<<"lib/elixir/lib/protocol.ex">>,
204205
<<"lib/elixir/lib/stream/reducers.ex">>,
205206
<<"lib/elixir/lib/enum.ex">>,
@@ -217,8 +218,7 @@ core_main() ->
217218
<<"lib/elixir/lib/kernel/error_handler.ex">>,
218219
<<"lib/elixir/lib/kernel/parallel_compiler.ex">>,
219220
<<"lib/elixir/lib/kernel/record_rewriter.ex">>,
220-
<<"lib/elixir/lib/kernel/lexical_tracker.ex">>,
221-
<<"lib/elixir/lib/module/locals_tracker.ex">>
221+
<<"lib/elixir/lib/kernel/lexical_tracker.ex">>
222222
].
223223

224224
binary_to_path({ModuleName, Binary}, CompilePath) ->

lib/elixir/src/elixir_def.erl

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -49,7 +49,7 @@ delete_definition(Module, Tuple) ->
4949
% Each function is then added to the function table.
5050

5151
store_definition(Line, Kind, CheckClauses, Call, Body, Pos) ->
52-
E = (elixir_env:get_cached(Pos))#elixir_env{line=Line},
52+
E = (elixir_locals:get_cached_env(Pos))#elixir_env{line=Line},
5353
{ NameAndArgs, Guards } = elixir_clauses:extract_guards(Call),
5454

5555
{ Name, Args } = case NameAndArgs of

lib/elixir/src/elixir_env.erl

Lines changed: 0 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,7 @@
11
-module(elixir_env).
22
-include("elixir.hrl").
33
-export([ex_to_env/1, env_to_scope/1, env_to_scope_with_vars/2, env_to_ex/1]).
4-
-export([cache/1, get_cached/1]).
54
-export([mergea/2, mergev/2]).
6-
-define(tracker, 'Elixir.Kernel.LexicalTracker').
75

86
%% Conversion in between #elixir_env, #elixir_scope and Macro.Env
97

@@ -38,20 +36,3 @@ mergev(E1, E2) ->
3836

3937
mergea(E1, E2) ->
4038
E2#elixir_env{vars=E1#elixir_env.vars}.
41-
42-
%% Caching
43-
44-
cache(#elixir_env{} = RE) ->
45-
E = RE#elixir_env{line=nil,vars=[]},
46-
case E#elixir_env.lexical_tracker of
47-
nil -> escape(E);
48-
Pid -> { Pid, ?tracker:cache(Pid, E) }
49-
end;
50-
cache(ExEnv) ->
51-
cache(ex_to_env(ExEnv)).
52-
53-
get_cached({Pid,Ref}) -> ?tracker:get_cached(Pid, Ref);
54-
get_cached(Env) -> Env.
55-
56-
escape(E) ->
57-
{ Escaped, _ } = elixir_quote:escape(E, false), Escaped.

lib/elixir/src/elixir_locals.erl

Lines changed: 19 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
11
%% Module responsible for tracking invocations of module calls.
22
-module(elixir_locals).
33
-export([
4-
setup/1, cleanup/1,
4+
setup/1, cleanup/1, cache_env/1, get_cached_env/1,
55
record_local/2, record_local/3, record_import/4,
66
record_definition/3, record_defaults/4,
77
ensure_no_function_conflict/4, warn_unused_local/3, format_error/1
@@ -123,6 +123,24 @@ if_tracker(Module, Callback) ->
123123
error:badarg -> false
124124
end.
125125

126+
%% CACHING
127+
128+
cache_env(#elixir_env{module=Module} = RE) ->
129+
E = RE#elixir_env{line=nil,vars=[]},
130+
try ets:lookup_element(Module, ?attr, 2) of
131+
Pid ->
132+
{ Pid, ?tracker:cache_env(Pid, E) }
133+
catch
134+
error:badarg ->
135+
{ Escaped, _ } = elixir_quote:escape(E, false),
136+
Escaped
137+
end;
138+
cache_env(ExEnv) ->
139+
cache_env(elixir_env:ex_to_env(ExEnv)).
140+
141+
get_cached_env({Pid,Ref}) -> ?tracker:get_cached_env(Pid, Ref);
142+
get_cached_env(Env) -> Env.
143+
126144
%% ERROR HANDLING
127145

128146
ensure_no_function_conflict(Meta, File, Module, AllDefined) ->

0 commit comments

Comments
 (0)