gsup: implement a (re-)connect the GSUP link if it fails

Change-Id: Id531d202ded123786d7a41dd0d7c3695af59fc2d
diff --git a/src/gsup_client.erl b/src/gsup_client.erl
index 047078b..967bf99 100644
--- a/src/gsup_client.erl
+++ b/src/gsup_client.erl
@@ -39,9 +39,13 @@
 -include_lib("osmo_ss7/include/ipa.hrl").
 
 -define(IPAC_PROTO_EXT_GSUP,	{osmo, 5}).
+-define(GSUP_TIMEOUT_MS, 5000).
 
 -record(gsupc_state, {
-	  	socket,
+		address,
+		port,
+		ccmoptions,
+		socket,
 		ipa_pid
 	 }).
 
@@ -54,43 +58,46 @@
 %% our exported API
 %% ------------------------------------------------------------------
 
-start_link(ServerAddr, ServerPort, Options) ->
-	gen_server:start_link(?MODULE, [ServerAddr, ServerPort, Options], [{debug, [trace]}]).
+start_link(ServerAddr, ServerPort, GsupName) ->
+	gen_server:start_link(?MODULE, [ServerAddr, ServerPort, GsupName], [{debug, [trace]}]).
 
 %% ------------------------------------------------------------------
 %% gen_server Function Definitions
 %% ------------------------------------------------------------------
 
-init([Address, Port, Options]) ->
+init([Address, Port, GsupName]) ->
 	ipa_proto:init(),
 	% register the GSUP codec with the IPA core; ignore result as we might be doing this multiple times
 	ipa_proto:register_codec(?IPAC_PROTO_EXT_GSUP, fun gsup_protocol:encode/1, fun gsup_protocol:decode/1),
-	connect([Address, Port, Options]).
-
-connect([Address, Port, Options]) ->
 	lager:info("Connecting to GSUP HLR on IP ~s port ~p~n", [Address, Port]),
-	CcmOptions = #ipa_ccm_options{
-		serial_number="HSS-00-00-00-00-00-00",
-		unit_id="0/0/0",
-		mac_address="00:00:00:00:00:00",
-		location="00:00:00:00:00:00",
-		unit_type="00:00:00:00:00:00",
-		equipment_version="00:00:00:00:00:00",
-		sw_version="00:00:00:00:00:00",
-		unit_name="HSS-00-00-00-00-00-00"
-		},
-	case ipa_proto:connect(Address, Port, Options) of
+        CcmOptions = #ipa_ccm_options{
+                serial_number=GsupName,
+                unit_id="0/0/0",
+                mac_address="00:00:00:00:00:00",
+                location="00:00:00:00:00:00",
+                unit_type="00:00:00:00:00:00",
+                equipment_version="00:00:00:00:00:00",
+                sw_version="00:00:00:00:00:00",
+                unit_name=GsupName
+                },
+        State = #gsupc_state{address = Address, port = Port, ccmoptions = CcmOptions, socket = [], ipa_pid = []},
+        case connect(State) of
+                {ok, State2} -> {ok, State2};
+                {error, _, State2} -> {ok, State2, ?GSUP_TIMEOUT_MS}
+        end.
+
+connect(State) ->
+        #gsupc_state{address = Address, port = Port, ccmoptions = Options} = State,
+	case ipa_proto:connect(Address, Port, []) of
 		{ok, {Socket, IpaPid}} ->
-			ipa_proto:set_ccm_options(Socket, CcmOptions),
+			ipa_proto:set_ccm_options(Socket, Options),
 			lager:info("connected!~n", []),
 			true = ipa_proto:register_stream(Socket, ?IPAC_PROTO_EXT_GSUP, {process_id, self()}),
 			ipa_proto:unblock(Socket),
-			{ok, #gsupc_state{socket=Socket, ipa_pid=IpaPid}};
-		{error, Reason} ->
-			lager:error("Connecting to GSUP HLR on IP ~s port ~p failed: ~p~n", [Address, Port, Reason]),
-			lager:info("Reconnecting to GSUP HLR in 5s...~n", []),
-			timer:sleep(5000),
-			connect([Address, Port, Options])
+			{ok, State#gsupc_state{socket=Socket, ipa_pid=IpaPid}};
+		{error, Error} ->
+	                lager:info("Failed to GSUP HLR on IP ~s port ~p ~p~n", [Address, Port, Error]),
+			{error, Error, State}
 	end.
 
 % send a given GSUP message and synchronously wait for message type ExpRes or ExpErr
@@ -102,10 +109,9 @@
 	receive
 		{ipa, Socket, ?IPAC_PROTO_EXT_GSUP, GsupMsgRx = #{message_type := ExpRes, imsi := Imsi}} ->
 			{reply, GsupMsgRx, State};
-
 		{ipa, Socket, ?IPAC_PROTO_EXT_GSUP, GsupMsgRx = #{message_type := ExpErr, imsi := Imsi}} ->
 			{reply, GsupMsgRx, State}
-	after 5000 ->
+	after ?GSUP_TIMEOUT_MS ->
 		{reply, timeout, State}
 	end.
 
@@ -114,8 +120,14 @@
 	{noreply, S}.
 
 handle_info({ipa_closed, _}, S) ->
-	lager:error("GSUP connection has been closed, supervisor should reconnect us"),
-	{stop, ipa_closed, S};
+	lager:error("GSUP connection has been closed, Reconnecting in 5sec."),
+	{noreply, S, ?GSUP_TIMEOUT_MS};
+handle_info(timeout, S) ->
+	case connect(S) of
+		{ok, State} -> {noreply, State};
+		{error, _, State} -> {noreply, State, ?GSUP_TIMEOUT_MS}
+	end;
+
 handle_info(Info, S) ->
 	error_logger:error_report(["unknown handle_info", {module, ?MODULE}, {info, Info}, {state, S}]),
 	{noreply, S}.
diff --git a/src/osmo_dia2gsup_sup.erl b/src/osmo_dia2gsup_sup.erl
index 17b5a14..03c780d 100644
--- a/src/osmo_dia2gsup_sup.erl
+++ b/src/osmo_dia2gsup_sup.erl
@@ -12,7 +12,7 @@
 	% GSUP side
 	HlrIp = application:get_env(osmo_dia2gsup, hlr_ip, "127.0.0.1"),
 	HlrPort = application:get_env(osmo_dia2gsup, hlr_port, 4222),
-	Args = [{local, gsup_client}, gsup_client, [HlrIp, HlrPort, []], [{debug, [trace]}]],
+	Args = [{local, gsup_client}, gsup_client, [HlrIp, HlrPort, "HSS-00-00-00-00-00-00"], [{debug, [trace]}]],
 	GsupChild = {gsup_client, {gen_server, start_link, Args}, permanent, 2000, worker, [gsup_client]},
 	% DIAMETER side
         DiaServer = {osmo_dia2gsup,{osmo_dia2gsup,start_link,[]},