[SCCP] Add (untested) parser routines for SCCP addresses (GT/SSN/PC)

We re-use the phone number digit parsing code from ISUP
diff --git a/src/isup_codec.erl b/src/isup_codec.erl
index 4a23c4b..fa21194 100644
--- a/src/isup_codec.erl
+++ b/src/isup_codec.erl
@@ -21,7 +21,7 @@
 -author('Harald Welte <laforge@gnumonks.org>').
 -include("isup.hrl").
 
--export([parse_isup_msg/1, encode_isup_msg/1]).
+-export([parse_isup_msg/1, encode_isup_msg/1, parse_isup_party/2]).
 
 -compile(export_all).
 
diff --git a/src/sccp.hrl b/src/sccp.hrl
index 26d5caa..7ee10b7 100644
--- a/src/sccp.hrl
+++ b/src/sccp.hrl
@@ -43,6 +43,31 @@
 -define(SCCP_PNC_IMPORTANCE,			18).
 -define(SCCP_PNC_LONG_DATA,			19).
 
+% According to Q.713 Section 3.4.1
+-define(SCCP_GTI_NO_GT,		2#0000).
+-define(SCCP_GTI_NAT_ONLY,	2#0001).
+-define(SCCP_GTI_TT_ONLY,	2#0010).
+-define(SCCP_GTI_TT_NP_ENC,	2#0011).
+-define(SCCP_GTI_TT_NP_ENC_NAT,	2#0100).
+
+% According to Q.731 Section 3.4.2.2
+-define(SCCP_SSN_UNKNOWN,	2#000000000).
+-define(SCCP_SSN_SCCP_MGMT,	2#000000001).
+-define(SCCP_SSN_ITU_T,		2#000000010).
+-define(SCCP_SSN_ISUP,		2#000000011).
+-define(SCCP_SSN_OAM,		2#000000100).
+-define(SCCP_SSN_MAP,		2#000000101).
+-define(SCCP_SSN_HLR,		2#000000110).
+-define(SCCP_SSN_VLR,		2#000000111).
+-define(SCCP_SSN_MSC,		2#000001000).
+-define(SCCP_SSN_EIR,		2#000001001).
+-define(SCCP_SSN_AUC,		2#000001010).
+-define(SCCP_SSN_ISDN_SS,	2#000001011).
+-define(SCCP_SSN_RES_NAT,	2#000001100).
+-define(SCCP_SSN_BISDN,		2#000001101).
+-define(SCCP_SSN_TC_TEST,	2#000001110).
+
+
 
 % a single parsed SCCP message
 -record(sccp_msg, {
diff --git a/src/sccp_codec.erl b/src/sccp_codec.erl
index f5854e1..62e5bdc 100644
--- a/src/sccp_codec.erl
+++ b/src/sccp_codec.erl
@@ -25,6 +25,78 @@
 
 -compile(export_all).
 
+parse_point_code(BinPC, PCind, OptListIn) when is_binary(BinPC),
+						is_list(OptListIn) ->
+	case PCind of
+		1 ->
+			<<PointCode:16/big, Remain/binary>> = BinPC,
+			OptListOut = OptListIn ++ [{point_code, PointCode}];
+		_ ->
+			Remain = BinPC,
+			OptListOut = OptListIn
+	end,
+	{Remain, OptListOut}.
+
+parse_ssn(BinSSN, SSNind, OptListIn) ->
+	case SSNind of
+		1 ->
+			<<SSN:8, Remain/binary>> = BinSSN,
+			OptListOut = OptListIn ++ [{ssn, SSN}];
+		_ ->
+			Remain = BinSSN,
+			OptListOut = OptListIn
+	end,
+	{Remain, OptListOut}.
+
+enc_is_odd(Enc) ->
+	case Enc of
+		1 -> 1;
+		_ -> 0
+	end.
+
+parse_gt(BinGT, GTind, OptListIn) ->
+	case GTind of
+		?SCCP_GTI_NO_GT ->
+			NewOpts = [];
+		?SCCP_GTI_NAT_ONLY ->
+			% Figure 7/Q.713
+			<<Odd:1, Nature:7, Digits/binary>> = BinGT,
+			PhoneNum = isup_codec:parse_isup_party(Digits, Odd),
+			NewOpts = [{nature_of_addr_ind, Nature},
+				   {phone_number, PhoneNum}];
+		?SCCP_GTI_TT_ONLY ->
+			% Figure 9/Q.913
+			<<TransType:8, Digits/binary>> = BinGT,
+			% Used in national interfaces only, we cannot parse Digits
+			NewOpts = [{trans_type, TransType}, {address, Digits}];
+		?SCCP_GTI_TT_NP_ENC ->
+			% Figure 10/Q.713
+			<<TransType:8, NumPlan:4, Enc:4, Digits/binary>> = BinGT,
+			PhoneNum = isup_codec:parse_isup_party(Digits, enc_is_odd(Enc)),
+			NewOpts = [{trans_type, TransType}, {encoding, Enc},
+				   {numbering_plan, NumPlan},
+				   {phone_number, PhoneNum}];
+		?SCCP_GTI_TT_NP_ENC_NAT ->
+			% Figure 11/Q.713
+			<<TransType:8, NumPlan:4, Enc:4, 0:1, Nature:7, Digits/binary>> = BinGT,
+			PhoneNum = isup_codec:parse_isup_party(Digits, enc_is_odd(Enc)),
+			NewOpts = [{trans_type, TransType}, {encoding, Enc},
+				   {numbering_plan, NumPlan},
+				   {nature_of_addr_ind, Nature},
+				   {phone_number, PhoneNum}];
+		_ ->
+			NewOpts = [{unknown, BinGT}]
+	end,
+	OptListIn ++ [{global_title, GTind, NewOpts}].
+
+% parse SCCP Address
+parse_sccp_addr(BinAddr) when is_binary(BinAddr) ->
+	<<ResNatUse:1, RoutInd:1, GTind:4, SSNind:1, PCind:1, Remain/binary>> = BinAddr,
+	OptList = [{reserved_national_use, ResNatUse}, {route_on_ssn, RoutInd}],
+	{RemainPC, OptPC} = parse_point_code(Remain, PCind, OptList),
+	{RemainSSN, OptSSN} = parse_ssn(RemainPC, SSNind, OptPC),
+	OptGT = parse_gt(RemainSSN, GTind, OptSSN),
+	OptGT.
 
 % parse SCCP Optional Part
 parse_sccp_opt(OptType, OptLen, Content) ->