File 2481-dtls-Use-enter-actions.patch of Package erlang

From 0d4047e02fe2275bdd8a8c940b3c79753e18cba2 Mon Sep 17 00:00:00 2001
From: Ingela Anderton Andin <ingela@erlang.org>
Date: Thu, 1 Jun 2017 23:34:51 +0200
Subject: [PATCH 1/2] dtls: Use enter actions

Using enter actions for retransmission timers makes the code easier to
understand. Previously the retransmission timer was incorrectly started in
the connection state. Using enter actions feels like a cleaner approach
than bloating the state with more flags.
---
 lib/ssl/src/dtls_connection.erl | 41 ++++++++++++++++++++++++++++++++---------
 1 file changed, 32 insertions(+), 9 deletions(-)

diff --git a/lib/ssl/src/dtls_connection.erl b/lib/ssl/src/dtls_connection.erl
index 2de947d8b..b19f976cd 100644
--- a/lib/ssl/src/dtls_connection.erl
+++ b/lib/ssl/src/dtls_connection.erl
@@ -115,7 +115,7 @@ send_handshake_flight(#state{socket = Socket,
     {Encoded, ConnectionStates} =
 	encode_handshake_flight(lists:reverse(Flight), Version, 1400, Epoch, ConnectionStates0),
     send(Transport, Socket, Encoded),
-    start_flight(State0#state{connection_states = ConnectionStates});
+    {State0#state{connection_states = ConnectionStates}, []};
 
 send_handshake_flight(#state{socket = Socket,
 			     transport_cb = Transport,
@@ -129,7 +129,7 @@ send_handshake_flight(#state{socket = Socket,
     {EncChangeCipher, ConnectionStates} = encode_change_cipher(ChangeCipher, Version, Epoch, ConnectionStates1),
 
     send(Transport, Socket, [HsBefore, EncChangeCipher]),
-    start_flight(State0#state{connection_states = ConnectionStates});
+    {State0#state{connection_states = ConnectionStates}, []};
 
 send_handshake_flight(#state{socket = Socket,
 			     transport_cb = Transport,
@@ -145,7 +145,7 @@ send_handshake_flight(#state{socket = Socket,
     {HsAfter, ConnectionStates} =
 	encode_handshake_flight(lists:reverse(Flight1), Version, 1400, Epoch, ConnectionStates2),
     send(Transport, Socket, [HsBefore, EncChangeCipher, HsAfter]),
-    start_flight(State0#state{connection_states = ConnectionStates});
+    {State0#state{connection_states = ConnectionStates}, []};
 
 send_handshake_flight(#state{socket = Socket,
 			     transport_cb = Transport,
@@ -159,7 +159,7 @@ send_handshake_flight(#state{socket = Socket,
     {HsAfter, ConnectionStates} =
 	encode_handshake_flight(lists:reverse(Flight1), Version, 1400, Epoch, ConnectionStates1),
     send(Transport, Socket, [EncChangeCipher, HsAfter]),
-    start_flight(State0#state{connection_states = ConnectionStates}).
+    {State0#state{connection_states = ConnectionStates}, []}.
 
 queue_change_cipher(ChangeCipher, #state{flight_buffer = Flight,
 					 connection_states = ConnectionStates0} = State) -> 
@@ -235,12 +235,14 @@ init([Role, Host, Port, Socket, Options,  User, CbInfo]) ->
     end.
 
 callback_mode() ->
-    state_functions.
+    [state_functions, state_enter].
 
 %%--------------------------------------------------------------------
 %% State functions 
 %%--------------------------------------------------------------------
 
+init(enter, _, State) ->
+    {keep_state, State};     
 init({call, From}, {start, Timeout}, 
      #state{host = Host, port = Port, role = client,
 	    ssl_options = SslOpts,
@@ -282,6 +284,8 @@ init({call, _} = Type, Event, #state{role = server} = State) ->
 init(Type, Event, State) ->
     ssl_connection:init(Type, Event, State, ?MODULE).
  
+error(enter, _, State) ->
+    {keep_state, State};     
 error({call, From}, {start, _Timeout}, {Error, State}) ->
     {stop_and_reply, normal, {reply, From, {error, Error}}, State};
 error({call, From}, Msg, State) ->
@@ -295,6 +299,11 @@ error(_, _, _) ->
 	    #state{}) ->
 		   gen_statem:state_function_result().
 %%--------------------------------------------------------------------
+hello(enter, _, #state{role = server} = State) ->
+    {keep_state, State};     
+hello(enter, _, #state{role = client} = State0) ->
+    {State, Actions} = handle_flight_timer(State0),
+    {keep_state, State, Actions}; 
 hello(internal, #client_hello{cookie = <<>>,
 			      client_version = Version} = Hello, #state{role = server,
 									transport_cb = Transport,
@@ -374,6 +383,9 @@ hello(state_timeout, Event, State) ->
 hello(Type, Event, State) ->
     ssl_connection:hello(Type, Event, State, ?MODULE).
 
+abbreviated(enter, _, State0) ->
+    {State, Actions} = handle_flight_timer(State0),
+    {keep_state, State, Actions}; 
 abbreviated(info, Event, State) ->
     handle_info(Event, abbreviated, State);
 abbreviated(internal = Type, 
@@ -391,6 +403,9 @@ abbreviated(state_timeout, Event, State) ->
 abbreviated(Type, Event, State) ->
     ssl_connection:abbreviated(Type, Event, State, ?MODULE).
 
+certify(enter, _, State0) ->
+    {State, Actions} = handle_flight_timer(State0),
+    {keep_state, State, Actions}; 
 certify(info, Event, State) ->
     handle_info(Event, certify, State);
 certify(internal = Type, #server_hello_done{} = Event, State) ->
@@ -400,6 +415,9 @@ certify(state_timeout, Event, State) ->
 certify(Type, Event, State) ->
     ssl_connection:certify(Type, Event, State, ?MODULE).
 
+cipher(enter, _, State0) ->
+    {State, Actions} = handle_flight_timer(State0),
+    {keep_state, State, Actions}; 
 cipher(info, Event, State) ->
     handle_info(Event, cipher, State);
 cipher(internal = Type, #change_cipher_spec{type = <<1>>} = Event,  
@@ -417,6 +435,8 @@ cipher(state_timeout, Event, State) ->
 cipher(Type, Event, State) ->
      ssl_connection:cipher(Type, Event, State, ?MODULE).
 
+connection(enter, _, State) ->
+    {keep_state, State};     
 connection(info, Event, State) ->
     handle_info(Event, connection, State);
 connection(internal, #hello_request{}, #state{host = Host, port = Port,
@@ -449,6 +469,9 @@ connection(internal, #client_hello{}, #state{role = server, allow_renegotiate =
 connection(Type, Event, State) ->
      ssl_connection:connection(Type, Event, State, ?MODULE).
 
+%%TODO does this make sense for DTLS ?
+downgrade(enter, _, State) ->
+    {keep_state, State};
 downgrade(Type, Event, State) ->
      ssl_connection:downgrade(Type, Event, State, ?MODULE).
 
@@ -841,13 +864,13 @@ next_flight(Flight) ->
 	    change_cipher_spec => undefined,
 	    handshakes_after_change_cipher_spec => []}.
 	
-start_flight(#state{transport_cb = gen_udp,
-		    flight_state = {retransmit, Timeout}} = State) ->
+handle_flight_timer(#state{transport_cb = gen_udp,
+                          flight_state = {retransmit, Timeout}} = State) ->
     start_retransmision_timer(Timeout, State);
-start_flight(#state{transport_cb = gen_udp,
+handle_flight_timer(#state{transport_cb = gen_udp,
 		    flight_state = connection} = State) ->
     {State, []};
-start_flight(State) ->
+handle_flight_timer(State) ->
     %% No retransmision needed i.e DTLS over SCTP
     {State#state{flight_state = reliable}, []}.
 
-- 
2.13.1

openSUSE Build Service is sponsored by