Use GSUP APN as Service-Selection field

Previous the osmo-hlr always sent a wildcard APN as the only APN
which violates the spec. Further wildcard APNs aren't support
by the current Open5gs.
Since I540132ee5dcfd09f4816e02e702927e1074ca50f the osmo-hlr
supports multiple APN in the subscriber data.

Related: SYS#6391
Change-Id: I2a0af5d785ce62968f6e3952602d92cb4f37e4ab
diff --git a/src/decode_apn.erl b/src/decode_apn.erl
new file mode 100644
index 0000000..ea12bc6
--- /dev/null
+++ b/src/decode_apn.erl
@@ -0,0 +1,51 @@
+
+-module(decode_apn).
+
+% decode APN Name Encoded Format
+% TS 23.003 APN
+-export([decode_apn/1, encode_apn/1]).
+
+decode_apn(ApnEnc) ->
+	decode_apn("", ApnEnc, 0).
+
+decode_apn(Result, [], 0) ->
+	Result;
+
+decode_apn(Result, << >>, 0) ->
+	Result;
+
+decode_apn("", ApnEnc, 0) ->
+	<< NewElemLen:8, RemainEnc/bytes >> = ApnEnc,
+	case NewElemLen of
+		0 -> "";
+		_ -> decode_apn("", RemainEnc, NewElemLen)
+	end;
+
+decode_apn(Result, ApnEnc, 0) ->
+	<< NewElemLen:8, RemainEnc/bytes >> = ApnEnc,
+	case NewElemLen of
+		0 -> Result;
+		_ -> decode_apn(Result ++ ".", RemainEnc, NewElemLen)
+	end;
+
+decode_apn(Result, ApnEnc, RemainLen) when RemainLen > 0 ->
+	<< Char:8, RemainEnc/bytes >> = ApnEnc,
+	decode_apn(Result ++ [Char], RemainEnc, RemainLen - 1).
+
+encode_apn(ApnStr) ->
+	encode_apn(<<>>, ApnStr, "", 0).
+
+encode_apn(ApnEnc, "", "", 0) ->
+	ApnEnc;
+
+encode_apn(ApnEnc, "", CurStr, Len) ->
+	CurBin = binary:list_to_bin(CurStr),
+	Result = << ApnEnc/binary, Len, CurBin/binary >>,
+	Result;
+
+encode_apn(ApnEnc, [ Char | RemainStr ], CurStr, Len) ->
+	case Char of
+		46 -> CurBin = binary:list_to_bin(CurStr),
+		       encode_apn(<<ApnEnc/binary, Len,  CurBin/binary >>, RemainStr, "", 0);
+		_ -> encode_apn(ApnEnc, RemainStr, CurStr ++ [Char], Len + 1)
+	end.
diff --git a/src/server_cb.erl b/src/server_cb.erl
index fc8e397..35dbb63 100644
--- a/src/server_cb.erl
+++ b/src/server_cb.erl
@@ -123,7 +123,7 @@
 gsup_pdp2dia(GsupPdpInfo) ->
 	#'PDP-Context'{'PDP-Type' = maps:get(pdp_type, GsupPdpInfo, ?PDP_TYPE_DEFAULT),
 		       'Context-Identifier' = maps:get(pdp_context_id, GsupPdpInfo),
-		       'Service-Selection' = maps:get(access_point_name, GsupPdpInfo),
+		       'Service-Selection' = decode_apn:decode_apn(maps:get(access_point_name, GsupPdpInfo)),
 		       'QoS-Subscribed' = maps:get(quality_of_service, GsupPdpInfo, ?PDP_QOS_DEFAULT)
 		      }.
 
@@ -149,7 +149,7 @@
 					      'Max-Requested-Bandwidth-DL' = 100000000},
 			     % The default APN Configuration shall not contain the Wildcard APN (see 3GPP TS
 			     % 23.003 [3], clause 9.2); the default APN shall always contain an explicit APN
-			     'Service-Selection' = "internet"%maps:get(access_point_name, GsupPdpInfo)
+			     'Service-Selection' = decode_apn:decode_apn(maps:get(access_point_name, GsupPdpInfo))
 			    }.
 
 % transient (only in Experimental-Result-Code)