aboutsummaryrefslogtreecommitdiffstats
path: root/lib
diff options
context:
space:
mode:
Diffstat (limited to 'lib')
-rw-r--r--lib/compiler/doc/src/compile.xml7
-rw-r--r--lib/compiler/src/beam_bsm.erl13
-rw-r--r--lib/compiler/src/compile.erl14
-rw-r--r--lib/compiler/src/sys_core_bsm.erl62
-rw-r--r--lib/compiler/test/bs_match_SUITE.erl38
-rw-r--r--lib/compiler/test/compile_SUITE.erl28
-rw-r--r--lib/inets/src/http_client/httpc_request.erl11
-rw-r--r--lib/inets/test/httpc_SUITE.erl75
-rw-r--r--lib/ssl/src/ssl_connection.erl48
-rw-r--r--lib/ssl/src/tls_connection.erl45
-rw-r--r--lib/ssl/src/tls_sender.erl17
-rw-r--r--lib/ssl/test/ssl_alpn_handshake_SUITE.erl23
-rw-r--r--lib/ssl/test/ssl_basic_SUITE.erl42
-rw-r--r--lib/ssl/test/ssl_certificate_verify_SUITE.erl54
-rw-r--r--lib/ssl/test/ssl_test_lib.erl38
-rw-r--r--lib/stdlib/doc/src/epp.xml8
-rw-r--r--lib/stdlib/src/epp.erl13
-rw-r--r--lib/stdlib/src/ms_transform.erl1
-rw-r--r--lib/stdlib/test/epp_SUITE.erl16
-rw-r--r--lib/stdlib/test/epp_SUITE_data/source_name.erl27
-rw-r--r--lib/stdlib/test/rand_SUITE.erl3
21 files changed, 423 insertions, 160 deletions
diff --git a/lib/compiler/doc/src/compile.xml b/lib/compiler/doc/src/compile.xml
index 1a71c83521..cfbd4c7fda 100644
--- a/lib/compiler/doc/src/compile.xml
+++ b/lib/compiler/doc/src/compile.xml
@@ -203,7 +203,8 @@
<tag><c>deterministic</c></tag>
<item>
<p>Omit the <c>options</c> and <c>source</c> tuples in
- the list returned by <c>Module:module_info(compile)</c>.
+ the list returned by <c>Module:module_info(compile)</c>, and
+ reduce the paths in stack traces to the module name alone.
This option will make it easier to achieve reproducible builds.
</p>
</item>
@@ -347,8 +348,8 @@ module.beam: module.erl \
<tag><c>{source,FileName}</c></tag>
<item>
- <p>Sets the value of the source, as returned by
- <c>module_info(compile)</c>.</p>
+ <p>Overrides the source file name as presented in
+ <c>module_info(compile)</c> and stack traces.</p>
</item>
<tag><c>{outdir,Dir}</c></tag>
diff --git a/lib/compiler/src/beam_bsm.erl b/lib/compiler/src/beam_bsm.erl
index abc6e96c85..1c8e0e9854 100644
--- a/lib/compiler/src/beam_bsm.erl
+++ b/lib/compiler/src/beam_bsm.erl
@@ -310,18 +310,7 @@ btb_reaches_match_2([{test,bs_start_match2,{f,F},Live,[Bin,_],Ctx}|Is],
end;
btb_reaches_match_2([{test,_,{f,F},Ss}=I|Is], Regs, D0) ->
btb_ensure_not_used(Ss, I, Regs),
- D1 = btb_follow_branch(F, Regs, D0),
- D = case Is of
- [{bs_context_to_binary,_}|_] ->
- %% bs_context_to_binary following a test instruction
- %% probably needs the current position to be saved as
- %% the new start position, but we can't be sure.
- %% Therefore, conservatively disable the optimization
- %% (instead of forcing a saving of the position).
- D1#btb{must_save=true,must_not_save=true};
- _ ->
- D1
- end,
+ D = btb_follow_branch(F, Regs, D0),
btb_reaches_match_1(Is, Regs, D);
btb_reaches_match_2([{test,_,{f,F},_,Ss,_}=I|Is], Regs, D0) ->
btb_ensure_not_used(Ss, I, Regs),
diff --git a/lib/compiler/src/compile.erl b/lib/compiler/src/compile.erl
index 562d57a6ef..6510571441 100644
--- a/lib/compiler/src/compile.erl
+++ b/lib/compiler/src/compile.erl
@@ -931,11 +931,17 @@ parse_module(_Code, St0) ->
end.
do_parse_module(DefEncoding, #compile{ifile=File,options=Opts,dir=Dir}=St) ->
+ SourceName0 = proplists:get_value(source, Opts, File),
+ SourceName = case member(deterministic, Opts) of
+ true -> filename:basename(SourceName0);
+ false -> SourceName0
+ end,
R = epp:parse_file(File,
- [{includes,[".",Dir|inc_paths(Opts)]},
- {macros,pre_defs(Opts)},
- {default_encoding,DefEncoding},
- extra]),
+ [{includes,[".",Dir|inc_paths(Opts)]},
+ {source_name, SourceName},
+ {macros,pre_defs(Opts)},
+ {default_encoding,DefEncoding},
+ extra]),
case R of
{ok,Forms,Extra} ->
Encoding = proplists:get_value(encoding, Extra),
diff --git a/lib/compiler/src/sys_core_bsm.erl b/lib/compiler/src/sys_core_bsm.erl
index d7b26c3a56..62657933ee 100644
--- a/lib/compiler/src/sys_core_bsm.erl
+++ b/lib/compiler/src/sys_core_bsm.erl
@@ -44,6 +44,14 @@ function([{#c_var{name={F,Arity}}=Name,B0}|Fs], FsAcc, Ws0) ->
{B,Ws} ->
function(Fs, [{Name,B}|FsAcc], Ws)
catch
+ throw:unsafe_bs_context_to_binary ->
+ %% Unsafe bs_context_to_binary (in the sense that the
+ %% contents of the binary will probably be wrong).
+ %% Disable binary optimizations for the entire function.
+ %% We don't generate an INFO message, because this happens
+ %% very infrequently and it would be hard to explain in
+ %% a comprehensible way in an INFO message.
+ function(Fs, [{Name,B0}|FsAcc], Ws0);
Class:Error:Stack ->
io:fwrite("Function: ~w/~w\n", [F,Arity]),
erlang:raise(Class, Error, Stack)
@@ -116,12 +124,66 @@ move_from_col(Pos, L) ->
[Col|First] ++ Rest.
bsm_do_an([#c_var{name=Vname}=V0|Vs0], Cs0, Case) ->
+ bsm_inner_context_to_binary(Cs0),
Cs = bsm_do_an_var(Vname, Cs0),
V = bsm_annotate_for_reuse(V0),
Vs = core_lib:make_values([V|Vs0]),
Case#c_case{arg=Vs,clauses=Cs};
bsm_do_an(_Vs, _Cs, Case) -> Case.
+bsm_inner_context_to_binary([#c_clause{body=B}|Cs]) ->
+ %% Consider:
+ %%
+ %% foo(<<Length, Data/binary>>) -> %Line 1
+ %% case {Data, Length} of %Line 2
+ %% {_, 0} -> Data; %Line 3
+ %% {<<...>>, 4} -> ... %Line 4
+ %% end.
+ %%
+ %% No sub binary will be created for Data in line 1. The match
+ %% context will be passed on to the `case` in line 2. In line 3,
+ %% this pass inserts a `bs_context_to_binary` instruction to
+ %% convert the match context representing Data to a binary before
+ %% returning it. The problem is that the binary created will be
+ %% the original binary (including the matched out Length field),
+ %% not the tail of the binary as it is supposed to be.
+ %%
+ %% Here follows a heuristic to disable the binary optimizations
+ %% for the entire function if this code kind of code is found.
+
+ case cerl_trees:free_variables(B) of
+ [] ->
+ %% Since there are no free variables in the body of
+ %% this clause, there can't be any troublesome
+ %% bs_context_to_binary instructions.
+ bsm_inner_context_to_binary(Cs);
+ [_|_]=Free ->
+ %% One of the free variables could refer to a match context
+ %% created by the outer binary match.
+ F = fun(#c_primop{name=#c_literal{val=bs_context_to_binary},
+ args=[#c_var{name=V}]}, _) ->
+ case member(V, Free) of
+ true ->
+ %% This bs_context_to_binary instruction will
+ %% make a binary of the match context from an
+ %% outer binary match. It is very likely that
+ %% the contents of the binary will be wrong
+ %% (the original binary as opposed to only
+ %% the tail binary).
+ throw(unsafe_bs_context_to_binary);
+ false ->
+ %% Safe. This bs_context_to_binary instruction
+ %% will make a binary from a match context
+ %% defined in the body of the clause.
+ ok
+ end;
+ (_, _) ->
+ ok
+ end,
+ cerl_trees:fold(F, ok, B)
+ end;
+bsm_inner_context_to_binary([]) -> ok.
+
bsm_do_an_var(V, [#c_clause{pats=[P|_],guard=G,body=B0}=C0|Cs]) ->
case P of
#c_var{name=VarName} ->
diff --git a/lib/compiler/test/bs_match_SUITE.erl b/lib/compiler/test/bs_match_SUITE.erl
index 7814738449..e97dbac8a6 100644
--- a/lib/compiler/test/bs_match_SUITE.erl
+++ b/lib/compiler/test/bs_match_SUITE.erl
@@ -1690,30 +1690,62 @@ non_opt_eq([], <<>>) ->
%% ERL-689
-erl_689(Config) ->
+erl_689(_Config) ->
{{0, 0, 0}, <<>>} = do_erl_689_1(<<0>>, ?MODULE),
{{2018, 8, 7}, <<>>} = do_erl_689_1(<<4,2018:16/little,8,7>>, ?MODULE),
{{0, 0, 0}, <<>>} = do_erl_689_2(?MODULE, <<0>>),
{{2018, 8, 7}, <<>>} = do_erl_689_2(?MODULE, <<4,2018:16/little,8,7>>),
ok.
-do_erl_689_1(<<Length, Data/binary>>, _) ->
+do_erl_689_1(Arg1, Arg2) ->
+ Res = do_erl_689_1a(Arg1, Arg2),
+ Res = do_erl_689_1b(Arg1, Arg2).
+
+do_erl_689_2(Arg1, Arg2) ->
+ Res = do_erl_689_2a(Arg1, Arg2),
+ Res = do_erl_689_2b(Arg1, Arg2).
+
+do_erl_689_1a(<<Length, Data/binary>>, _) ->
+ case {Data, Length} of
+ {_, 0} ->
+ %% bs_context_to_binary would incorrectly set Data to the original
+ %% binary (before matching in the function head).
+ {{0, 0, 0}, Data};
+ {<<Y:16/little, M, D, Rest/binary>>, 4} ->
+ {{Y, M, D}, Rest}
+ end.
+
+do_erl_689_1b(<<Length, Data/binary>>, _) ->
case {Data, Length} of
{_, 0} ->
%% bs_context_to_binary would incorrectly set Data to the original
%% binary (before matching in the function head).
+ id(0),
{{0, 0, 0}, Data};
{<<Y:16/little, M, D, Rest/binary>>, 4} ->
+ id(1),
+ {{Y, M, D}, Rest}
+ end.
+
+do_erl_689_2a(_, <<Length, Data/binary>>) ->
+ case {Length, Data} of
+ {0, _} ->
+ %% bs_context_to_binary would incorrectly set Data to the original
+ %% binary (before matching in the function head).
+ {{0, 0, 0}, Data};
+ {4, <<Y:16/little, M, D, Rest/binary>>} ->
{{Y, M, D}, Rest}
end.
-do_erl_689_2(_, <<Length, Data/binary>>) ->
+do_erl_689_2b(_, <<Length, Data/binary>>) ->
case {Length, Data} of
{0, _} ->
%% bs_context_to_binary would incorrectly set Data to the original
%% binary (before matching in the function head).
+ id(0),
{{0, 0, 0}, Data};
{4, <<Y:16/little, M, D, Rest/binary>>} ->
+ id(1),
{{Y, M, D}, Rest}
end.
diff --git a/lib/compiler/test/compile_SUITE.erl b/lib/compiler/test/compile_SUITE.erl
index 1ecae06128..6b230710b3 100644
--- a/lib/compiler/test/compile_SUITE.erl
+++ b/lib/compiler/test/compile_SUITE.erl
@@ -36,7 +36,7 @@
core_roundtrip/1, asm/1, optimized_guards/1,
sys_pre_attributes/1, dialyzer/1,
warnings/1, pre_load_check/1, env_compiler_options/1,
- bc_options/1, deterministic_include/1
+ bc_options/1, deterministic_include/1, deterministic_paths/1
]).
suite() -> [{ct_hooks,[ts_install_cth]}].
@@ -53,7 +53,7 @@ all() ->
cover, env, core_pp, core_roundtrip, asm, optimized_guards,
sys_pre_attributes, dialyzer, warnings, pre_load_check,
env_compiler_options, custom_debug_info, bc_options,
- custom_compile_info, deterministic_include].
+ custom_compile_info, deterministic_include, deterministic_paths].
groups() ->
[].
@@ -1531,6 +1531,30 @@ deterministic_include(Config) when is_list(Config) ->
ok.
+deterministic_paths(Config) when is_list(Config) ->
+ DataDir = proplists:get_value(data_dir, Config),
+
+ %% Files without +deterministic should differ if they were compiled from a
+ %% different directory.
+ true = deterministic_paths_1(DataDir, "simple", []),
+
+ %% ... but files with +deterministic shouldn't.
+ false = deterministic_paths_1(DataDir, "simple", [deterministic]),
+
+ ok.
+
+deterministic_paths_1(DataDir, Name, Opts) ->
+ Simple = filename:join(DataDir, "simple"),
+ {ok, Cwd} = file:get_cwd(),
+ try
+ {ok,_,A} = compile:file(Simple, [binary | Opts]),
+ ok = file:set_cwd(DataDir),
+ {ok,_,B} = compile:file(Name, [binary | Opts]),
+ A =/= B
+ after
+ file:set_cwd(Cwd)
+ end.
+
%%%
%%% Utilities.
%%%
diff --git a/lib/inets/src/http_client/httpc_request.erl b/lib/inets/src/http_client/httpc_request.erl
index 4cb2d57b14..0f20d93bc1 100644
--- a/lib/inets/src/http_client/httpc_request.erl
+++ b/lib/inets/src/http_client/httpc_request.erl
@@ -223,7 +223,8 @@ update_headers(Headers, ContentType, Body, []) ->
%% that does not include a message body. This implies that either the
%% Content-Length or the Transfer-Encoding header MUST be present.
%% DO NOT send content-type when Body is empty.
- Headers#http_request_h{'content-type' = ContentType};
+ Headers1 = Headers#http_request_h{'content-type' = ContentType},
+ handle_transfer_encoding(Headers1);
_ ->
Headers#http_request_h{
'content-length' = body_length(Body),
@@ -232,6 +233,14 @@ update_headers(Headers, ContentType, Body, []) ->
update_headers(_, _, _, HeadersAsIs) ->
HeadersAsIs.
+handle_transfer_encoding(Headers = #http_request_h{'transfer-encoding' = undefined}) ->
+ Headers;
+handle_transfer_encoding(Headers) ->
+ %% RFC7230 3.3.2
+ %% A sender MUST NOT send a 'Content-Length' header field in any message
+ %% that contains a 'Transfer-Encoding' header field.
+ Headers#http_request_h{'content-length' = undefined}.
+
body_length(Body) when is_binary(Body) ->
integer_to_list(size(Body));
diff --git a/lib/inets/test/httpc_SUITE.erl b/lib/inets/test/httpc_SUITE.erl
index 89a90b62f3..8357e02014 100644
--- a/lib/inets/test/httpc_SUITE.erl
+++ b/lib/inets/test/httpc_SUITE.erl
@@ -171,7 +171,8 @@ misc() ->
server_does_not_exist,
timeout_memory_leak,
wait_for_whole_response,
- post_204_chunked
+ post_204_chunked,
+ chunkify_fun
].
sim_mixed() ->
@@ -1409,7 +1410,8 @@ post_204_chunked(_Config) ->
{ok, ListenSocket} = gen_tcp:listen(0, [{active,once}, binary]),
{ok,{_,Port}} = inet:sockname(ListenSocket),
- spawn(fun () -> custom_server(Msg, Chunk, ListenSocket) end),
+ spawn(fun () -> custom_server(Msg, Chunk, ListenSocket,
+ fun post_204_receive/0) end),
{ok,Host} = inet:gethostname(),
End = "/cgi-bin/erl/httpd_example:post_204",
@@ -1419,16 +1421,26 @@ post_204_chunked(_Config) ->
%% Second request times out in the faulty case.
{ok, _} = httpc:request(post, {URL, [], "text/html", []}, [], []).
-custom_server(Msg, Chunk, ListenSocket) ->
+post_204_receive() ->
+ receive
+ {tcp, _, Msg} ->
+ ct:log("Message received: ~p", [Msg])
+ after
+ 1000 ->
+ ct:fail("Timeout: did not recive packet")
+ end.
+
+%% Custom server is used to test special cases when using chunked encoding
+custom_server(Msg, Chunk, ListenSocket, ReceiveFun) ->
{ok, Accept} = gen_tcp:accept(ListenSocket),
- receive_packet(),
+ ReceiveFun(),
send_response(Msg, Chunk, Accept),
- custom_server_loop(Msg, Chunk, Accept).
+ custom_server_loop(Msg, Chunk, Accept, ReceiveFun).
-custom_server_loop(Msg, Chunk, Accept) ->
- receive_packet(),
+custom_server_loop(Msg, Chunk, Accept, ReceiveFun) ->
+ ReceiveFun(),
send_response(Msg, Chunk, Accept),
- custom_server_loop(Msg, Chunk, Accept).
+ custom_server_loop(Msg, Chunk, Accept, ReceiveFun).
send_response(Msg, Chunk, Socket) ->
inet:setopts(Socket, [{active, once}]),
@@ -1436,15 +1448,54 @@ send_response(Msg, Chunk, Socket) ->
timer:sleep(250),
gen_tcp:send(Socket, Chunk).
-receive_packet() ->
+%%--------------------------------------------------------------------
+chunkify_fun() ->
+ [{doc,"Test that a chunked encoded request does not include the 'Content-Length header'"}].
+chunkify_fun(_Config) ->
+ Msg = "HTTP/1.1 204 No Content\r\n" ++
+ "Date: Thu, 23 Aug 2018 13:36:29 GMT\r\n" ++
+ "Content-Type: text/html\r\n" ++
+ "Server: inets/6.5.2.3\r\n" ++
+ "Cache-Control: no-cache\r\n" ++
+ "Pragma: no-cache\r\n" ++
+ "Expires: Fri, 24 Aug 2018 07:49:35 GMT\r\n" ++
+ "Transfer-Encoding: chunked\r\n" ++
+ "\r\n",
+ Chunk = "0\r\n\r\n",
+
+ {ok, ListenSocket} = gen_tcp:listen(0, [{active,once}, binary]),
+ {ok,{_,Port}} = inet:sockname(ListenSocket),
+ spawn(fun () -> custom_server(Msg, Chunk, ListenSocket,
+ fun chunkify_receive/0) end),
+
+ {ok,Host} = inet:gethostname(),
+ End = "/cgi-bin/erl/httpd_example",
+ URL = ?URL_START ++ Host ++ ":" ++ integer_to_list(Port) ++ End,
+ Fun = fun(_) -> {ok,<<1>>,eof_body} end,
+ Acc = start,
+
+ {ok, {{_,204,_}, _, _}} =
+ httpc:request(put, {URL, [], "text/html", {chunkify, Fun, Acc}}, [], []).
+
+chunkify_receive() ->
+ Error = "HTTP/1.1 500 Internal Server Error\r\n" ++
+ "Content-Length: 0\r\n\r\n",
receive
- {tcp, _, Msg} ->
- ct:log("Message received: ~p", [Msg])
+ {tcp, Port, Msg} ->
+ case binary:match(Msg, <<"content-length">>) of
+ nomatch ->
+ ct:log("Message received: ~s", [binary_to_list(Msg)]);
+ {_, _} ->
+ ct:log("Message received (negative): ~s", [binary_to_list(Msg)]),
+ %% Signal a testcase failure when the received HTTP request
+ %% contains a 'Content-Length' header.
+ gen_tcp:send(Port, Error),
+ ct:fail("Content-Length present in received headers.")
+ end
after
1000 ->
ct:fail("Timeout: did not recive packet")
end.
-
%%--------------------------------------------------------------------
stream_fun_server_close() ->
[{doc, "Test that an error msg is received when using a receiver fun as stream target"}].
diff --git a/lib/ssl/src/ssl_connection.erl b/lib/ssl/src/ssl_connection.erl
index 5ea1924d40..9f876add6c 100644
--- a/lib/ssl/src/ssl_connection.erl
+++ b/lib/ssl/src/ssl_connection.erl
@@ -334,17 +334,12 @@ prf(ConnectionPid, Secret, Label, Seed, WantedLength) ->
%%====================================================================
%% Alert and close handling
%%====================================================================
-handle_own_alert(Alert, Version, StateName,
+handle_own_alert(Alert, _, StateName,
#state{role = Role,
- transport_cb = Transport,
- socket = Socket,
protocol_cb = Connection,
- connection_states = ConnectionStates,
ssl_options = SslOpts} = State) ->
try %% Try to tell the other side
- {BinMsg, _} =
- Connection:encode_alert(Alert, Version, ConnectionStates),
- Connection:send(Transport, Socket, BinMsg)
+ send_alert(Alert, StateName, State)
catch _:_ -> %% Can crash if we are in a uninitialized state
ignore
end,
@@ -1160,24 +1155,20 @@ handle_call({close, {Pid, Timeout}}, From, StateName, State0, Connection) when i
%% we must recive the close alert from the peer before releasing the
%% transport socket.
{next_state, downgrade, State#state{terminated = true}, [{timeout, Timeout, downgrade}]};
-handle_call({close, _} = Close, From, StateName, State, Connection) ->
+handle_call({close, _} = Close, From, StateName, State, _Connection) ->
%% Run terminate before returning so that the reuseaddr
%% inet-option works properly
- Result = Connection:terminate(Close, StateName, State#state{terminated = true}),
+ Result = terminate(Close, StateName, State),
stop_and_reply(
{shutdown, normal},
- {reply, From, Result}, State);
-handle_call({shutdown, How0}, From, _,
+ {reply, From, Result}, State#state{terminated = true});
+handle_call({shutdown, How0}, From, StateName,
#state{transport_cb = Transport,
- negotiated_version = Version,
- connection_states = ConnectionStates,
- socket = Socket} = State, Connection) ->
+ socket = Socket} = State, _) ->
case How0 of
How when How == write; How == both ->
- Alert = ?ALERT_REC(?WARNING, ?CLOSE_NOTIFY),
- {BinMsg, _} =
- Connection:encode_alert(Alert, Version, ConnectionStates),
- Connection:send(Transport, Socket, BinMsg);
+ send_alert(?ALERT_REC(?WARNING, ?CLOSE_NOTIFY),
+ StateName, State);
_ ->
ok
end,
@@ -1343,14 +1334,20 @@ terminate({shutdown, own_alert}, _StateName, #state{
_ ->
Connection:close({timeout, ?DEFAULT_TIMEOUT}, Socket, Transport, undefined, undefined)
end;
+terminate(downgrade = Reason, connection, #state{protocol_cb = Connection,
+ transport_cb = Transport, socket = Socket
+ } = State) ->
+ handle_trusted_certs_db(State),
+ Connection:close(Reason, Socket, Transport, undefined, undefined);
terminate(Reason, connection, #state{protocol_cb = Connection,
- connection_states = ConnectionStates,
- ssl_options = #ssl_options{padding_check = Check},
- transport_cb = Transport, socket = Socket
- } = State) ->
+ connection_states = ConnectionStates,
+ ssl_options = #ssl_options{padding_check = Check},
+ transport_cb = Transport, socket = Socket
+ } = State) ->
handle_trusted_certs_db(State),
Alert = terminate_alert(Reason),
- ok = Connection:send_alert_in_connection(Alert, State),
+ %% Send the termination ALERT if possible
+ catch (ok = Connection:send_alert_in_connection(Alert, State)),
Connection:close(Reason, Socket, Transport, ConnectionStates, Check);
terminate(Reason, _StateName, #state{transport_cb = Transport, protocol_cb = Connection,
socket = Socket
@@ -1387,6 +1384,11 @@ format_status(terminate, [_, StateName, State]) ->
%%--------------------------------------------------------------------
%%% Internal functions
%%--------------------------------------------------------------------
+send_alert(Alert, connection, #state{protocol_cb = Connection} = State) ->
+ Connection:send_alert_in_connection(Alert, State);
+send_alert(Alert, _, #state{protocol_cb = Connection} = State) ->
+ Connection:send_alert(Alert, State).
+
connection_info(#state{sni_hostname = SNIHostname,
session = #session{session_id = SessionId,
cipher_suite = CipherSuite, ecc = ECCCurve},
diff --git a/lib/ssl/src/tls_connection.erl b/lib/ssl/src/tls_connection.erl
index 2fde17a0fd..adb4f6d9ea 100644
--- a/lib/ssl/src/tls_connection.erl
+++ b/lib/ssl/src/tls_connection.erl
@@ -56,7 +56,9 @@
empty_connection_state/2]).
%% Alert and close handling
--export([send_alert/2, send_alert_in_connection/2, encode_alert/3, close/5, protocol_name/0]).
+-export([send_alert/2, send_alert_in_connection/2,
+ send_sync_alert/2,
+ encode_alert/3, close/5, protocol_name/0]).
%% Data handling
-export([encode_data/3, passive_receive/2, next_record_if_active/1,
@@ -346,16 +348,34 @@ encode_alert(#alert{} = Alert, Version, ConnectionStates) ->
send_alert(Alert, #state{negotiated_version = Version,
socket = Socket,
- protocol_cb = Connection,
transport_cb = Transport,
connection_states = ConnectionStates0} = StateData0) ->
{BinMsg, ConnectionStates} =
- Connection:encode_alert(Alert, Version, ConnectionStates0),
- Connection:send(Transport, Socket, BinMsg),
+ encode_alert(Alert, Version, ConnectionStates0),
+ send(Transport, Socket, BinMsg),
StateData0#state{connection_states = ConnectionStates}.
-send_alert_in_connection(Alert, #state{protocol_specific = #{sender := Sender}}) ->
+%% If an ALERT sent in the connection state, should cause the TLS
+%% connection to end, we need to synchronize with the tls_sender
+%% process so that the ALERT if possible (that is the tls_sender process is
+%% not blocked) is sent before the connection process terminates and
+%% thereby closes the transport socket.
+send_alert_in_connection(#alert{level = ?FATAL} = Alert, State) ->
+ send_sync_alert(Alert, State);
+send_alert_in_connection(#alert{description = ?CLOSE_NOTIFY} = Alert, State) ->
+ send_sync_alert(Alert, State);
+send_alert_in_connection(Alert,
+ #state{protocol_specific = #{sender := Sender}}) ->
tls_sender:send_alert(Sender, Alert).
+send_sync_alert(Alert, #state{protocol_specific = #{sender := Sender}}= State) ->
+ tls_sender:send_and_ack_alert(Sender, Alert),
+ receive
+ {Sender, ack_alert} ->
+ ok
+ after ?DEFAULT_TIMEOUT ->
+ %% Sender is blocked terminate anyway
+ throw({stop, {shutdown, own_alert}, State})
+ end.
%% User closes or recursive call!
close({close, Timeout}, Socket, Transport = gen_tcp, _,_) ->
@@ -505,7 +525,9 @@ hello(internal, #client_hello{client_version = ClientVersion} = Hello,
case tls_handshake:hello(Hello, SslOpts, {Port, Session0, Cache, CacheCb,
ConnectionStates0, Cert, KeyExAlg}, Renegotiation) of
#alert{} = Alert ->
- ssl_connection:handle_own_alert(Alert, ClientVersion, hello, State);
+ ssl_connection:handle_own_alert(Alert, ClientVersion, hello,
+ State#state{negotiated_version
+ = ClientVersion});
{Version, {Type, Session},
ConnectionStates, Protocol0, ServerHelloExt, HashSign} ->
Protocol = case Protocol0 of
@@ -528,7 +550,8 @@ hello(internal, #server_hello{} = Hello,
ssl_options = SslOptions} = State) ->
case tls_handshake:hello(Hello, SslOptions, ConnectionStates0, Renegotiation) of
#alert{} = Alert ->
- ssl_connection:handle_own_alert(Alert, ReqVersion, hello, State);
+ ssl_connection:handle_own_alert(Alert, ReqVersion, hello,
+ State#state{negotiated_version = ReqVersion});
{Version, NewId, ConnectionStates, ProtoExt, Protocol} ->
ssl_connection:handle_session(Hello,
Version, NewId, ConnectionStates, ProtoExt, Protocol, State)
@@ -636,8 +659,8 @@ callback_mode() ->
state_functions.
terminate(Reason, StateName, State) ->
- ensure_sender_terminate(Reason, State),
- catch ssl_connection:terminate(Reason, StateName, State).
+ catch ssl_connection:terminate(Reason, StateName, State),
+ ensure_sender_terminate(Reason, State).
format_status(Type, Data) ->
ssl_connection:format_status(Type, Data).
@@ -788,8 +811,8 @@ handle_info({CloseTag, Socket}, StateName,
%% and then receive the final message.
next_event(StateName, no_record, State)
end;
-handle_info({'EXIT', Pid, Reason}, _,
- #state{protocol_specific = Pid} = State) ->
+handle_info({'EXIT', Sender, Reason}, _,
+ #state{protocol_specific = #{sender := Sender}} = State) ->
{stop, {shutdown, sender_died, Reason}, State};
handle_info(Msg, StateName, State) ->
ssl_connection:StateName(info, Msg, State, ?MODULE).
diff --git a/lib/ssl/src/tls_sender.erl b/lib/ssl/src/tls_sender.erl
index db67d7ddff..ec03000b33 100644
--- a/lib/ssl/src/tls_sender.erl
+++ b/lib/ssl/src/tls_sender.erl
@@ -28,7 +28,8 @@
-include("ssl_api.hrl").
%% API
--export([start/0, start/1, initialize/2, send_data/2, send_alert/2, renegotiate/1,
+-export([start/0, start/1, initialize/2, send_data/2, send_alert/2,
+ send_and_ack_alert/2, renegotiate/1,
update_connection_state/3, dist_tls_socket/1, dist_handshake_complete/3]).
%% gen_statem callbacks
@@ -89,13 +90,21 @@ send_data(Pid, AppData) ->
%%--------------------------------------------------------------------
-spec send_alert(pid(), #alert{}) -> _.
-%% Description: TLS connection process wants to end an Alert
+%% Description: TLS connection process wants to send an Alert
%% in the connection state.
%%--------------------------------------------------------------------
send_alert(Pid, Alert) ->
gen_statem:cast(Pid, Alert).
%%--------------------------------------------------------------------
+-spec send_and_ack_alert(pid(), #alert{}) -> ok.
+%% Description: TLS connection process wants to send an Alert
+%% in the connection state and recive an ack.
+%%--------------------------------------------------------------------
+send_and_ack_alert(Pid, Alert) ->
+ gen_statem:cast(Pid, {ack_alert, Alert}).
+
+%%--------------------------------------------------------------------
-spec renegotiate(pid()) -> {ok, WriteState::map()} | {error, closed}.
%% Description: So TLS connection process can synchronize the
%% encryption state to be used when handshaking.
@@ -207,6 +216,10 @@ connection({call, From}, {dist_handshake_complete, _Node, DHandle}, #data{connec
process_flag(priority, normal),
Events = dist_data_events(DHandle, []),
{next_state, ?FUNCTION_NAME, StateData#data{dist_handle = DHandle}, [{reply, From, ok} | Events]};
+connection(cast, {ack_alert, #alert{} = Alert}, #data{connection_pid = Pid} =StateData0) ->
+ StateData = send_tls_alert(Alert, StateData0),
+ Pid ! {self(), ack_alert},
+ {next_state, ?FUNCTION_NAME, StateData};
connection(cast, #alert{} = Alert, StateData0) ->
StateData = send_tls_alert(Alert, StateData0),
{next_state, ?FUNCTION_NAME, StateData};
diff --git a/lib/ssl/test/ssl_alpn_handshake_SUITE.erl b/lib/ssl/test/ssl_alpn_handshake_SUITE.erl
index 27062d4801..04c4b257d9 100644
--- a/lib/ssl/test/ssl_alpn_handshake_SUITE.erl
+++ b/lib/ssl/test/ssl_alpn_handshake_SUITE.erl
@@ -155,7 +155,7 @@ empty_client(Config) when is_list(Config) ->
run_failing_handshake(Config,
[{alpn_advertised_protocols, []}],
[{alpn_preferred_protocols, [<<"spdy/2">>, <<"spdy/3">>, <<"http/2">>]}],
- {connect_failed,{tls_alert,"no application protocol"}}).
+ {error,{tls_alert,"no application protocol"}}).
%--------------------------------------------------------------------------------
@@ -163,7 +163,7 @@ empty_server(Config) when is_list(Config) ->
run_failing_handshake(Config,
[{alpn_advertised_protocols, [<<"http/1.0">>, <<"http/1.1">>]}],
[{alpn_preferred_protocols, []}],
- {connect_failed,{tls_alert,"no application protocol"}}).
+ {error,{tls_alert,"no application protocol"}}).
%--------------------------------------------------------------------------------
@@ -171,7 +171,7 @@ empty_client_empty_server(Config) when is_list(Config) ->
run_failing_handshake(Config,
[{alpn_advertised_protocols, []}],
[{alpn_preferred_protocols, []}],
- {connect_failed,{tls_alert,"no application protocol"}}).
+ {error,{tls_alert,"no application protocol"}}).
%--------------------------------------------------------------------------------
@@ -179,7 +179,7 @@ no_matching_protocol(Config) when is_list(Config) ->
run_failing_handshake(Config,
[{alpn_advertised_protocols, [<<"http/1.0">>, <<"http/1.1">>]}],
[{alpn_preferred_protocols, [<<"spdy/2">>, <<"spdy/3">>, <<"http/2">>]}],
- {connect_failed,{tls_alert,"no application protocol"}}).
+ {error,{tls_alert,"no application protocol"}}).
%--------------------------------------------------------------------------------
@@ -342,18 +342,19 @@ run_failing_handshake(Config, ClientExtraOpts, ServerExtraOpts, ExpectedResult)
ServerOpts = ServerExtraOpts ++ ssl_test_lib:ssl_options(server_rsa_opts, Config),
{ClientNode, ServerNode, Hostname} = ssl_test_lib:run_where(Config),
- Server = ssl_test_lib:start_server([{node, ServerNode}, {port, 0},
+ Server = ssl_test_lib:start_server_error([{node, ServerNode}, {port, 0},
{from, self()},
{mfa, {?MODULE, placeholder, []}},
{options, ServerOpts}]),
Port = ssl_test_lib:inet_port(Server),
- ExpectedResult
- = ssl_test_lib:start_client([{node, ClientNode}, {port, Port},
- {host, Hostname},
- {from, self()},
- {mfa, {?MODULE, placeholder, []}},
- {options, ClientOpts}]).
+ Client = ssl_test_lib:start_client_error([{node, ClientNode}, {port, Port},
+ {host, Hostname},
+ {from, self()},
+ {mfa, {?MODULE, placeholder, []}},
+ {options, ClientOpts}]),
+ ssl_test_lib:check_result(Server, ExpectedResult,
+ Client, ExpectedResult).
run_handshake(Config, ClientExtraOpts, ServerExtraOpts, ExpectedProtocol) ->
Data = "hello world",
diff --git a/lib/ssl/test/ssl_basic_SUITE.erl b/lib/ssl/test/ssl_basic_SUITE.erl
index cae491b882..4585ea7306 100644
--- a/lib/ssl/test/ssl_basic_SUITE.erl
+++ b/lib/ssl/test/ssl_basic_SUITE.erl
@@ -1183,16 +1183,16 @@ fallback(Config) when is_list(Config) ->
Port = ssl_test_lib:inet_port(Server),
- Client =
- ssl_test_lib:start_client_error([{node, ClientNode},
- {port, Port}, {host, Hostname},
- {from, self()}, {options,
- [{fallback, true},
- {versions, ['tlsv1']}
- | ClientOpts]}]),
+ Client =
+ ssl_test_lib:start_client_error([{node, ClientNode},
+ {port, Port}, {host, Hostname},
+ {from, self()}, {options,
+ [{fallback, true},
+ {versions, ['tlsv1']}
+ | ClientOpts]}]),
- ssl_test_lib:check_result(Server, {error,{tls_alert,"inappropriate fallback"}},
- Client, {error,{tls_alert,"inappropriate fallback"}}).
+ ssl_test_lib:check_result(Server, {error,{tls_alert,"inappropriate fallback"}},
+ Client, {error,{tls_alert,"inappropriate fallback"}}).
%%--------------------------------------------------------------------
cipher_format() ->
@@ -2645,14 +2645,14 @@ default_reject_anonymous(Config) when is_list(Config) ->
{options, ServerOpts}]),
Port = ssl_test_lib:inet_port(Server),
Client = ssl_test_lib:start_client_error([{node, ClientNode}, {port, Port},
- {host, Hostname},
- {from, self()},
- {options,
- [{ciphers,[CipherSuite]} |
- ClientOpts]}]),
+ {host, Hostname},
+ {from, self()},
+ {options,
+ [{ciphers,[CipherSuite]} |
+ ClientOpts]}]),
ssl_test_lib:check_result(Server, {error, {tls_alert, "insufficient security"}},
- Client, {error, {tls_alert, "insufficient security"}}).
+ Client, {error, {tls_alert, "insufficient security"}}).
%%--------------------------------------------------------------------
ciphers_ecdsa_signed_certs() ->
@@ -3605,14 +3605,14 @@ no_common_signature_algs(Config) when is_list(Config) ->
| ServerOpts]}]),
Port = ssl_test_lib:inet_port(Server),
Client = ssl_test_lib:start_client_error([{node, ClientNode}, {port, Port},
- {host, Hostname},
- {from, self()},
- {options, [{signature_algs, [{sha384, rsa}]}
- | ClientOpts]}]),
+ {host, Hostname},
+ {from, self()},
+ {options, [{signature_algs, [{sha384, rsa}]}
+ | ClientOpts]}]),
ssl_test_lib:check_result(Server, {error, {tls_alert, "insufficient security"}},
- Client, {error, {tls_alert, "insufficient security"}}).
-
+ Client, {error, {tls_alert, "insufficient security"}}).
+
%%--------------------------------------------------------------------
tls_dont_crash_on_handshake_garbage() ->
diff --git a/lib/ssl/test/ssl_certificate_verify_SUITE.erl b/lib/ssl/test/ssl_certificate_verify_SUITE.erl
index b387feb97a..588ca153a9 100644
--- a/lib/ssl/test/ssl_certificate_verify_SUITE.erl
+++ b/lib/ssl/test/ssl_certificate_verify_SUITE.erl
@@ -620,8 +620,8 @@ cert_expired(Config) when is_list(Config) ->
{from, self()},
{options, [{verify, verify_peer}, {active, Active} | ClientOpts]}]),
- tcp_delivery_workaround(Server, {error, {tls_alert, "certificate expired"}},
- Client, {error, {tls_alert, "certificate expired"}}).
+ ssl_test_lib:check_result(Server, {error, {tls_alert, "certificate expired"}},
+ Client, {error, {tls_alert, "certificate expired"}}).
two_digits_str(N) when N < 10 ->
lists:flatten(io_lib:format("0~p", [N]));
@@ -729,8 +729,8 @@ critical_extension_verify_server(Config) when is_list(Config) ->
%% This certificate has a critical extension that we don't
%% understand. Therefore, verification should fail.
- tcp_delivery_workaround(Server, {error, {tls_alert, "unsupported certificate"}},
- Client, {error, {tls_alert, "unsupported certificate"}}),
+ ssl_test_lib:check_result(Server, {error, {tls_alert, "unsupported certificate"}},
+ Client, {error, {tls_alert, "unsupported certificate"}}),
ssl_test_lib:close(Server).
%%--------------------------------------------------------------------
@@ -909,8 +909,8 @@ invalid_signature_server(Config) when is_list(Config) ->
{from, self()},
{options, [{verify, verify_peer} | ClientOpts]}]),
- tcp_delivery_workaround(Server, {error, {tls_alert, "unknown ca"}},
- Client, {error, {tls_alert, "unknown ca"}}).
+ ssl_test_lib:check_result(Server, {error, {tls_alert, "unknown ca"}},
+ Client, {error, {tls_alert, "unknown ca"}}).
%%--------------------------------------------------------------------
@@ -946,8 +946,8 @@ invalid_signature_client(Config) when is_list(Config) ->
{from, self()},
{options, NewClientOpts}]),
- tcp_delivery_workaround(Server, {error, {tls_alert, "unknown ca"}},
- Client, {error, {tls_alert, "unknown ca"}}).
+ ssl_test_lib:check_result(Server, {error, {tls_alert, "unknown ca"}},
+ Client, {error, {tls_alert, "unknown ca"}}).
%%--------------------------------------------------------------------
@@ -1236,41 +1236,3 @@ incomplete_chain(Config) when is_list(Config) ->
%% Internal functions ------------------------------------------------
%%--------------------------------------------------------------------
-tcp_delivery_workaround(Server, ServerMsg, Client, ClientMsg) ->
- receive
- {Server, ServerMsg} ->
- client_msg(Client, ClientMsg);
- {Client, ClientMsg} ->
- server_msg(Server, ServerMsg);
- {Client, {error,closed}} ->
- server_msg(Server, ServerMsg);
- {Server, {error,closed}} ->
- client_msg(Client, ClientMsg)
- end.
-
-client_msg(Client, ClientMsg) ->
- receive
- {Client, ClientMsg} ->
- ok;
- {Client, {error,closed}} ->
- ct:log("client got close"),
- ok;
- {Client, {error, Reason}} ->
- ct:log("client got econnaborted: ~p", [Reason]),
- ok;
- Unexpected ->
- ct:fail(Unexpected)
- end.
-server_msg(Server, ServerMsg) ->
- receive
- {Server, ServerMsg} ->
- ok;
- {Server, {error,closed}} ->
- ct:log("server got close"),
- ok;
- {Server, {error, Reason}} ->
- ct:log("server got econnaborted: ~p", [Reason]),
- ok;
- Unexpected ->
- ct:fail(Unexpected)
- end.
diff --git a/lib/ssl/test/ssl_test_lib.erl b/lib/ssl/test/ssl_test_lib.erl
index f3235f5614..39a5bcaad6 100644
--- a/lib/ssl/test/ssl_test_lib.erl
+++ b/lib/ssl/test/ssl_test_lib.erl
@@ -1003,7 +1003,6 @@ ecc_test_error(COpts, SOpts, CECCOpts, SECCOpts, Config) ->
Error = {error, {tls_alert, "insufficient security"}},
check_result(Server, Error, Client, Error).
-
start_client(openssl, Port, ClientOpts, Config) ->
Cert = proplists:get_value(certfile, ClientOpts),
Key = proplists:get_value(keyfile, ClientOpts),
@@ -2061,3 +2060,40 @@ hardcode_dsa_key(3) ->
y = 48598545580251057979126570873881530215432219542526130654707948736559463436274835406081281466091739849794036308281564299754438126857606949027748889019480936572605967021944405048011118039171039273602705998112739400664375208228641666852589396502386172780433510070337359132965412405544709871654840859752776060358,
x = 1457508827177594730669011716588605181448418352823}.
+tcp_delivery_workaround(Server, ServerMsg, Client, ClientMsg) ->
+ receive
+ {Server, ServerMsg} ->
+ client_msg(Client, ClientMsg);
+ {Client, ClientMsg} ->
+ server_msg(Server, ServerMsg);
+ {Client, {error,closed}} ->
+ server_msg(Server, ServerMsg);
+ {Server, {error,closed}} ->
+ client_msg(Client, ClientMsg)
+ end.
+client_msg(Client, ClientMsg) ->
+ receive
+ {Client, ClientMsg} ->
+ ok;
+ {Client, {error,closed}} ->
+ ct:log("client got close"),
+ ok;
+ {Client, {error, Reason}} ->
+ ct:log("client got econnaborted: ~p", [Reason]),
+ ok;
+ Unexpected ->
+ ct:fail(Unexpected)
+ end.
+server_msg(Server, ServerMsg) ->
+ receive
+ {Server, ServerMsg} ->
+ ok;
+ {Server, {error,closed}} ->
+ ct:log("server got close"),
+ ok;
+ {Server, {error, Reason}} ->
+ ct:log("server got econnaborted: ~p", [Reason]),
+ ok;
+ Unexpected ->
+ ct:fail(Unexpected)
+ end.
diff --git a/lib/stdlib/doc/src/epp.xml b/lib/stdlib/doc/src/epp.xml
index 1dc0161398..d803d259aa 100644
--- a/lib/stdlib/doc/src/epp.xml
+++ b/lib/stdlib/doc/src/epp.xml
@@ -124,6 +124,10 @@
<fsummary>Open a file for preprocessing.</fsummary>
<desc>
<p>Opens a file for preprocessing.</p>
+ <p>If you want to change the file name of the implicit -file()
+ attributes inserted during preprocessing, you can do with
+ <c>{source_name, <anno>SourceName</anno>}</c>. If unset it will
+ default to the name of the opened file.</p>
<p>If <c>extra</c> is specified in
<c><anno>Options</anno></c>, the return value is
<c>{ok, <anno>Epp</anno>, <anno>Extra</anno>}</c> instead
@@ -169,6 +173,10 @@
<p>Preprocesses and parses an Erlang source file.
Notice that tuple <c>{eof, <anno>Line</anno>}</c> returned at the
end of the file is included as a "form".</p>
+ <p>If you want to change the file name of the implicit -file()
+ attributes inserted during preprocessing, you can do with
+ <c>{source_name, <anno>SourceName</anno>}</c>. If unset it will
+ default to the name of the opened file.</p>
<p>If <c>extra</c> is specified in
<c><anno>Options</anno></c>, the return value is
<c>{ok, [<anno>Form</anno>], <anno>Extra</anno>}</c> instead
diff --git a/lib/stdlib/src/epp.erl b/lib/stdlib/src/epp.erl
index cc34d4bdd3..181a524db6 100644
--- a/lib/stdlib/src/epp.erl
+++ b/lib/stdlib/src/epp.erl
@@ -117,6 +117,7 @@ open(Name, File, StartLocation, Path, Pdm) ->
{'ok', Epp} | {'ok', Epp, Extra} | {'error', ErrorDescriptor} when
Options :: [{'default_encoding', DefEncoding :: source_encoding()} |
{'includes', IncludePath :: [DirectoryName :: file:name()]} |
+ {'source_name', SourceName :: file:name()} |
{'macros', PredefMacros :: macros()} |
{'name',FileName :: file:name()} |
'extra'],
@@ -248,6 +249,7 @@ parse_file(Ifile, Path, Predefs) ->
{'ok', [Form]} | {'ok', [Form], Extra} | {error, OpenError} when
FileName :: file:name(),
Options :: [{'includes', IncludePath :: [DirectoryName :: file:name()]} |
+ {'source_name', SourceName :: file:name()} |
{'macros', PredefMacros :: macros()} |
{'default_encoding', DefEncoding :: source_encoding()} |
'extra'],
@@ -540,9 +542,10 @@ server(Pid, Name, Options, #epp{pre_opened=PreOpened}=St) ->
init_server(Pid, Name, Options, St)
end.
-init_server(Pid, Name, Options, St0) ->
+init_server(Pid, FileName, Options, St0) ->
+ SourceName = proplists:get_value(source_name, Options, FileName),
Pdm = proplists:get_value(macros, Options, []),
- Ms0 = predef_macros(Name),
+ Ms0 = predef_macros(FileName),
case user_predef(Pdm, Ms0) of
{ok,Ms1} ->
#epp{file = File, location = AtLocation} = St0,
@@ -552,14 +555,14 @@ init_server(Pid, Name, Options, St0) ->
epp_reply(Pid, {ok,self(),Encoding}),
%% ensure directory of current source file is
%% first in path
- Path = [filename:dirname(Name) |
+ Path = [filename:dirname(FileName) |
proplists:get_value(includes, Options, [])],
- St = St0#epp{delta=0, name=Name, name2=Name,
+ St = St0#epp{delta=0, name=SourceName, name2=SourceName,
path=Path, macs=Ms1,
default_encoding=DefEncoding},
From = wait_request(St),
Anno = erl_anno:new(AtLocation),
- enter_file_reply(From, file_name(Name), Anno,
+ enter_file_reply(From, file_name(SourceName), Anno,
AtLocation, code),
wait_req_scan(St);
{error,E} ->
diff --git a/lib/stdlib/src/ms_transform.erl b/lib/stdlib/src/ms_transform.erl
index 3845e35e9b..6d243e1bec 100644
--- a/lib/stdlib/src/ms_transform.erl
+++ b/lib/stdlib/src/ms_transform.erl
@@ -946,6 +946,7 @@ real_guard_function(node,0) -> true;
real_guard_function(node,1) -> true;
real_guard_function(round,1) -> true;
real_guard_function(size,1) -> true;
+real_guard_function(bit_size,1) -> true;
real_guard_function(map_size,1) -> true;
real_guard_function(map_get,2) -> true;
real_guard_function(tl,1) -> true;
diff --git a/lib/stdlib/test/epp_SUITE.erl b/lib/stdlib/test/epp_SUITE.erl
index a3e294ffea..0ac99ad03a 100644
--- a/lib/stdlib/test/epp_SUITE.erl
+++ b/lib/stdlib/test/epp_SUITE.erl
@@ -29,7 +29,7 @@
otp_8562/1, otp_8665/1, otp_8911/1, otp_10302/1, otp_10820/1,
otp_11728/1, encoding/1, extends/1, function_macro/1,
test_error/1, test_warning/1, otp_14285/1,
- test_if/1]).
+ test_if/1,source_name/1]).
-export([epp_parse_erl_form/2]).
@@ -70,7 +70,7 @@ all() ->
overload_mac, otp_8388, otp_8470, otp_8562,
otp_8665, otp_8911, otp_10302, otp_10820, otp_11728,
encoding, extends, function_macro, test_error, test_warning,
- otp_14285, test_if].
+ otp_14285, test_if, source_name].
groups() ->
[{upcase_mac, [], [upcase_mac_1, upcase_mac_2]},
@@ -1702,6 +1702,18 @@ function_macro(Config) ->
ok.
+source_name(Config) when is_list(Config) ->
+ DataDir = proplists:get_value(data_dir, Config),
+ File = filename:join(DataDir, "source_name.erl"),
+
+ source_name_1(File, "/test/gurka.erl"),
+ source_name_1(File, "gaffel.erl"),
+
+ ok.
+
+source_name_1(File, Expected) ->
+ Res = epp:parse_file(File, [{source_name, Expected}]),
+ {ok, [{attribute,_,file,{Expected,_}} | _Forms]} = Res.
check(Config, Tests) ->
eval_tests(Config, fun check_test/2, Tests).
diff --git a/lib/stdlib/test/epp_SUITE_data/source_name.erl b/lib/stdlib/test/epp_SUITE_data/source_name.erl
new file mode 100644
index 0000000000..71ad2dddb9
--- /dev/null
+++ b/lib/stdlib/test/epp_SUITE_data/source_name.erl
@@ -0,0 +1,27 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2018. 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.
+%% You may obtain a copy of the License at
+%%
+%% http://www.apache.org/licenses/LICENSE-2.0
+%%
+%% Unless required by applicable law or agreed to in writing, software
+%% distributed under the License is distributed on an "AS IS" BASIS,
+%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+%% See the License for the specific language governing permissions and
+%% limitations under the License.
+%%
+%% %CopyrightEnd%
+%%
+
+-module(source_name).
+-export([ok/0]).
+
+%% Changing source name should not affect headers
+-include("bar.hrl").
+
+ok() -> ok.
diff --git a/lib/stdlib/test/rand_SUITE.erl b/lib/stdlib/test/rand_SUITE.erl
index d753d929f5..b76c9f5341 100644
--- a/lib/stdlib/test/rand_SUITE.erl
+++ b/lib/stdlib/test/rand_SUITE.erl
@@ -475,10 +475,11 @@ stats_standard_normal_box_muller_2(Config) when is_list(Config) ->
stats_standard_normal(Config) when is_list(Config) ->
+ Retries = 7,
try math:erfc(1.0) of
_ ->
stats_standard_normal(
- fun rand:normal_s/1, rand:seed_s(exrop), 3)
+ fun rand:normal_s/1, rand:seed_s(exrop), Retries)
catch error:_ ->
{skip, "math:erfc/1 not supported"}
end.