Skip to content

Commit 29f2eb7

Browse files
committed
Merge pull request #2801 from fishcakez/app_env
Move application state out of application env
2 parents a3754e3 + 0bb3d1c commit 29f2eb7

31 files changed

+654
-284
lines changed

lib/elixir/lib/code.ex

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -325,7 +325,7 @@ defmodule Code do
325325
Check `compiler_options/1` for more information.
326326
"""
327327
def compiler_options do
328-
:elixir_code_server.call :compiler_options
328+
:elixir_config.get :compiler_options
329329
end
330330

331331
@doc """
@@ -364,7 +364,8 @@ defmodule Code do
364364
bad = bad |> Keyword.keys |> Enum.join(", ")
365365
raise ArgumentError, message: "unknown compiler options: #{bad}"
366366
end
367-
:elixir_code_server.cast {:compiler_options, opts}
367+
update = &:orddict.merge(fn(_, _, value) -> value end, &1, opts)
368+
:elixir_config.update :compiler_options, update
368369
end
369370

370371
@doc """

lib/elixir/lib/kernel/cli.ex

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -56,7 +56,7 @@ defmodule Kernel.CLI do
5656
## Helpers
5757

5858
defp at_exit(res) do
59-
hooks = :elixir_code_server.call(:flush_at_exit)
59+
hooks = :elixir_config.get_and_put(:at_exit, [])
6060
res = Enum.reduce(hooks, res, &exec_fun/2)
6161
if hooks == [], do: res, else: at_exit(res)
6262
end

lib/elixir/lib/system.ex

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -72,7 +72,7 @@ defmodule System do
7272
"""
7373
@spec argv() :: [String.t]
7474
def argv do
75-
:elixir_code_server.call :argv
75+
:elixir_config.get(:argv)
7676
end
7777

7878
@doc """
@@ -83,7 +83,7 @@ defmodule System do
8383
"""
8484
@spec argv([String.t]) :: :ok
8585
def argv(args) do
86-
:elixir_code_server.cast({:argv, args})
86+
:elixir_config.put(:argv, args)
8787
end
8888

8989
@doc """
@@ -224,7 +224,7 @@ defmodule System do
224224
The function must receive the exit status code as an argument.
225225
"""
226226
def at_exit(fun) when is_function(fun, 1) do
227-
:elixir_code_server.cast {:at_exit, fun}
227+
:elixir_config.update :at_exit, &[fun|&1]
228228
end
229229

230230
@doc """

lib/elixir/lib/uri.ex

Lines changed: 12 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -11,18 +11,17 @@ defmodule URI do
1111

1212
import Bitwise
1313

14-
@ports %{
15-
"ftp" => 21,
16-
"http" => 80,
17-
"https" => 443,
18-
"ldap" => 389,
19-
"sftp" => 22,
20-
"tftp" => 69,
21-
}
22-
23-
Enum.each @ports, fn {scheme, port} ->
14+
@schemes [
15+
"ftp",
16+
"http",
17+
"https",
18+
"ldap",
19+
"sftp",
20+
"tftp",
21+
]
22+
23+
Enum.each @schemes, fn scheme ->
2424
def normalize_scheme(unquote(scheme)), do: unquote(scheme)
25-
def default_port(unquote(scheme)), do: unquote(port)
2625
end
2726

2827
@doc """
@@ -47,8 +46,7 @@ defmodule URI do
4746
4847
"""
4948
def default_port(scheme) when is_binary(scheme) do
50-
{:ok, dict} = Application.fetch_env(:elixir, :uri)
51-
Map.get(dict, scheme)
49+
:elixir_config.get({:uri, scheme})
5250
end
5351

5452
@doc """
@@ -59,8 +57,7 @@ defmodule URI do
5957
new URIs.
6058
"""
6159
def default_port(scheme, port) when is_binary(scheme) and port > 0 do
62-
{:ok, dict} = Application.fetch_env(:elixir, :uri)
63-
Application.put_env(:elixir, :uri, Map.put(dict, scheme, port), persistent: true)
60+
:elixir_config.put({:uri, scheme}, port)
6461
end
6562

6663
@doc """

lib/elixir/src/elixir.erl

Lines changed: 22 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -42,10 +42,29 @@ start(_Type, _Args) ->
4242
ok
4343
end,
4444

45-
elixir_sup:start_link().
45+
URIs = [{<<"ftp">>, 21},
46+
{<<"sftp">>, 22},
47+
{<<"tftp">>, 69},
48+
{<<"http">>, 80},
49+
{<<"https">>, 443},
50+
{<<"ldap">>, 389}],
51+
URIConfig = [{{uri, Scheme}, Port} || {Scheme, Port} <- URIs],
52+
CompilerOpts = [{docs,true},{debug_info,true},{warnings_as_errors,false}],
53+
Config = [{at_exit, []},
54+
{compiler_options, orddict:from_list(CompilerOpts)}
55+
| URIConfig],
56+
Tab = elixir_config:new(Config),
57+
case elixir_sup:start_link() of
58+
{ok, Sup} ->
59+
{ok, Sup, Tab};
60+
{error, _Reason} = Error ->
61+
elixir_config:delete(Tab),
62+
Error
63+
end.
64+
65+
stop(Tab) ->
66+
elixir_config:delete(Tab).
4667

47-
stop(_S) ->
48-
ok.
4968

5069
config_change(_Changed, _New, _Remove) ->
5170
ok.

lib/elixir/src/elixir_code_server.erl

Lines changed: 3 additions & 57 deletions
Original file line numberDiff line numberDiff line change
@@ -6,15 +6,11 @@
66

77
-define(timeout, 30000).
88
-record(elixir_code_server, {
9-
argv=[],
109
loaded=[],
11-
at_exit=[],
1210
paths={[],[]},
1311
mod_pool={[],0},
1412
mod_ets=dict:new(),
15-
compilation_status=[],
16-
compiler_options=[{docs,true},{debug_info,true},{warnings_as_errors,false}],
17-
erl_compiler_options=nil
13+
compilation_status=[]
1814
}).
1915

2016
call(Args) ->
@@ -61,18 +57,6 @@ handle_call({acquire, Path}, From, Config) ->
6157
handle_call(loaded, _From, Config) ->
6258
{reply, [F || {F, true} <- Config#elixir_code_server.loaded], Config};
6359

64-
handle_call(at_exit, _From, Config) ->
65-
{reply, Config#elixir_code_server.at_exit, Config};
66-
67-
handle_call(flush_at_exit, _From, Config) ->
68-
{reply, Config#elixir_code_server.at_exit, Config#elixir_code_server{at_exit=[]}};
69-
70-
handle_call(argv, _From, Config) ->
71-
{reply, Config#elixir_code_server.argv, Config};
72-
73-
handle_call(compiler_options, _From, Config) ->
74-
{reply, Config#elixir_code_server.compiler_options, Config};
75-
7660
handle_call({compilation_status, CompilerPid}, _From, Config) ->
7761
CompilationStatusList = Config#elixir_code_server.compilation_status,
7862
CompilationStatusListNew = orddict:erase(CompilerPid, CompilationStatusList),
@@ -88,35 +72,17 @@ handle_call(retrieve_module_name, _From, Config) ->
8872
{reply, module_tuple(Counter), Config#elixir_code_server{mod_pool={[],Counter+1}}}
8973
end;
9074

91-
handle_call(erl_compiler_options, _From, Config) ->
92-
case Config#elixir_code_server.erl_compiler_options of
93-
nil ->
94-
Opts = erl_compiler_options(),
95-
{reply, Opts, Config#elixir_code_server{erl_compiler_options=Opts}};
96-
Opts ->
97-
{reply, Opts, Config}
98-
end;
99-
10075
handle_call(paths, _From, Config) ->
10176
{reply, Config#elixir_code_server.paths, Config};
10277

10378
handle_call(Request, _From, Config) ->
10479
{stop, {badcall, Request}, Config}.
10580

106-
handle_cast({at_exit, AtExit}, Config) ->
107-
{noreply, Config#elixir_code_server{at_exit=[AtExit|Config#elixir_code_server.at_exit]}};
108-
109-
handle_cast({argv, Argv}, Config) ->
110-
{noreply, Config#elixir_code_server{argv=Argv}};
111-
112-
handle_cast({compiler_options, Options}, Config) ->
113-
Final = orddict:merge(fun(_,_,V) -> V end, Config#elixir_code_server.compiler_options, Options),
114-
{noreply, Config#elixir_code_server{compiler_options=Final}};
115-
11681
handle_cast({register_warning, CompilerPid}, Config) ->
11782
CompilationStatusCurrent = Config#elixir_code_server.compilation_status,
11883
CompilationStatusNew = orddict:store(CompilerPid, error, CompilationStatusCurrent),
119-
case orddict:find(warnings_as_errors, Config#elixir_code_server.compiler_options) of
84+
CompilerOptions = elixir_config:get(compiler_options),
85+
case orddict:find(warnings_as_errors, CompilerOptions) of
12086
{ok, true} -> {noreply, Config#elixir_code_server{compilation_status=CompilationStatusNew}};
12187
_ -> {noreply, Config}
12288
end;
@@ -183,23 +149,3 @@ undefmodule(Ref, #elixir_code_server{mod_ets=ModEts} = Config) ->
183149
error ->
184150
Config
185151
end.
186-
187-
erl_compiler_options() ->
188-
Key = "ERL_COMPILER_OPTIONS",
189-
case os:getenv(Key) of
190-
false -> [];
191-
Str when is_list(Str) ->
192-
case erl_scan:string(Str) of
193-
{ok,Tokens,_} ->
194-
case erl_parse:parse_term(Tokens ++ [{dot, 1}]) of
195-
{ok,List} when is_list(List) -> List;
196-
{ok,Term} -> [Term];
197-
{error,_Reason} ->
198-
io:format("Ignoring bad term in ~ts\n", [Key]),
199-
[]
200-
end;
201-
{error, {_,_,_Reason}, _} ->
202-
io:format("Ignoring bad term in ~ts\n", [Key]),
203-
[]
204-
end
205-
end.

lib/elixir/src/elixir_compiler.erl

Lines changed: 38 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,7 @@
66
%% Public API
77

88
get_opt(Key) ->
9-
Dict = elixir_code_server:call(compiler_options),
9+
Dict = elixir_config:get(compiler_options),
1010
case lists:keyfind(Key, 1, Dict) of
1111
false -> false;
1212
{Key, Value} -> Value
@@ -78,7 +78,7 @@ code_loading_compilation(Forms, Vars, #{line := Line} = E) ->
7878

7979
%% Pass {native, false} to speed up bootstrap
8080
%% process when native is set to true
81-
AllOpts = elixir_code_server:call(erl_compiler_options),
81+
AllOpts = options(),
8282
FinalOpts = AllOpts -- [native, warn_missing_spec],
8383
inner_module(Form, FinalOpts, true, E, fun(_, Binary) ->
8484
%% If we have labeled locals, anonymous functions
@@ -92,6 +92,36 @@ code_loading_compilation(Forms, Vars, #{line := Line} = E) ->
9292
dispatch_loaded(Module, Fun, Args, Purgeable, I, EE)
9393
end).
9494

95+
options() ->
96+
case elixir_config:get(erl_compiler_options) of
97+
nil ->
98+
elixir_config:update(erl_compiler_options, fun options/1);
99+
Opts ->
100+
Opts
101+
end.
102+
103+
options(nil) ->
104+
Key = "ERL_COMPILER_OPTIONS",
105+
case os:getenv(Key) of
106+
false -> [];
107+
Str when is_list(Str) ->
108+
case erl_scan:string(Str) of
109+
{ok,Tokens,_} ->
110+
case erl_parse:parse_term(Tokens ++ [{dot, 1}]) of
111+
{ok,List} when is_list(List) -> List;
112+
{ok,Term} -> [Term];
113+
{error,_Reason} ->
114+
io:format("Ignoring bad term in ~ts\n", [Key]),
115+
[]
116+
end;
117+
{error, {_,_,_Reason}, _} ->
118+
io:format("Ignoring bad term in ~ts\n", [Key]),
119+
[]
120+
end
121+
end;
122+
options(Opts) ->
123+
Opts.
124+
95125
dispatch_loaded(Module, Fun, Args, Purgeable, I, E) ->
96126
Res = Module:Fun(Args),
97127
code:delete(Module),
@@ -142,8 +172,8 @@ module(Forms, Opts, E, Callback) ->
142172
Final =
143173
case (get_opt(debug_info) == true) orelse
144174
lists:member(debug_info, Opts) of
145-
true -> [debug_info] ++ elixir_code_server:call(erl_compiler_options);
146-
false -> elixir_code_server:call(erl_compiler_options)
175+
true -> [debug_info] ++ options();
176+
false -> options()
147177
end,
148178
inner_module(Forms, Final, false, E, Callback).
149179

@@ -177,7 +207,10 @@ no_auto_import() ->
177207

178208
core() ->
179209
{ok, _} = application:ensure_all_started(elixir),
180-
elixir_code_server:cast({compiler_options, [{docs,false},{internal,true}]}),
210+
New = orddict:from_list([{docs,false},{internal,true}]),
211+
Merge = fun(_, _, Value) -> Value end,
212+
Update = fun(Old) -> orddict:merge(Merge, Old, New) end,
213+
_ = elixir_config:update(compiler_options, Update),
181214
[core_file(File) || File <- core_main()].
182215

183216
core_file(File) ->

lib/elixir/src/elixir_config.erl

Lines changed: 65 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,65 @@
1+
-module(elixir_config).
2+
-compile({no_auto_import, [get/1]}).
3+
-export([new/1, delete/1, put/2, get/1, update/2, get_and_put/2]).
4+
-export([start_link/0, init/1, handle_call/3, handle_cast/2,
5+
handle_info/2, code_change/3, terminate/2]).
6+
-behaviour(gen_server).
7+
8+
%% public api
9+
10+
new(Opts) ->
11+
Tab = ets:new(?MODULE, [named_table, public, {read_concurrency, true}]),
12+
true = ets:insert_new(?MODULE, Opts),
13+
Tab.
14+
15+
delete(?MODULE) ->
16+
ets:delete(?MODULE).
17+
18+
put(Key, Value) ->
19+
gen_server:call(?MODULE, {put, Key, Value}).
20+
21+
get(Key) ->
22+
case ets:lookup(?MODULE, Key) of
23+
[{_, Value}] -> Value;
24+
[] -> nil
25+
end.
26+
27+
update(Key, Fun) ->
28+
gen_server:call(?MODULE, {update, Key, Fun}).
29+
30+
get_and_put(Key, Value) ->
31+
gen_server:call(?MODULE, {get_and_put, Key, Value}).
32+
33+
start_link() ->
34+
gen_server:start_link({local, ?MODULE}, ?MODULE, ?MODULE, []).
35+
36+
%% gen_server api
37+
38+
init(Tab) ->
39+
%% Ets table must be writable
40+
public = ets:info(Tab, protection),
41+
{ok, Tab}.
42+
43+
handle_call({put, Key, Value}, _From, Tab) ->
44+
ets:insert(Tab, {Key, Value}),
45+
{reply, ok, Tab};
46+
handle_call({update, Key, Fun}, _From, Tab) ->
47+
Value = Fun(get(Key)),
48+
ets:insert(Tab, {Key, Value}),
49+
{reply, Value, Tab};
50+
handle_call({get_and_put, Key, Value}, _From, Tab) ->
51+
OldValue = get(Key),
52+
ets:insert(Tab, {Key, Value}),
53+
{reply, OldValue, Tab}.
54+
55+
handle_cast(Cast, Tab) ->
56+
{stop, {bad_cast, Cast}, Tab}.
57+
58+
handle_info(_Msg, Tab) ->
59+
{noreply, Tab}.
60+
61+
code_change(_OldVsn, Tab, _Extra) ->
62+
{ok, Tab}.
63+
64+
terminate(_Reason, _Tab) ->
65+
ok.

lib/elixir/src/elixir_sup.erl

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,16 @@ start_link() ->
77

88
init(ok) ->
99
Workers = [
10+
{
11+
elixir_config,
12+
{elixir_config, start_link, []},
13+
14+
permanent, % Restart = permanent | transient | temporary
15+
2000, % Shutdown = brutal_kill | int() >= 0 | infinity
16+
worker, % Type = worker | supervisor
17+
[elixir_config] % Modules = [Module] | dynamic
18+
},
19+
1020
{
1121
elixir_code_server,
1222
{elixir_code_server, start_link, []},

0 commit comments

Comments
 (0)