summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorHarald Welte <laforge@gnumonks.org>2011-04-16 20:14:38 +0200
committerHarald Welte <laforge@gnumonks.org>2011-04-16 20:14:38 +0200
commit21c6b9427191b062aa81a55c046eeba8659b5e9c (patch)
tree223a97a717e251c0150cd32c0f21108421d07041
parenta87c64ab0c24a0c96f3090dd84830025b2d3e6d0 (diff)
MAP: Fix-up after asn1ct automatic 1990->1994 EXTERNAL conversion
So what the Erlang asn1ct does is: Decode the incoming EXTERNAL type, convert it to the 1994 format and hand it to the user program. The encoder is opposite: Take what the user supplies (in our case 1994) and then transform it to 1990 before handing it to the actual encoder function. The only problem is: The 1994 format does only support OCTET STRING as actual embedded data type, whereas the 1990 format can also indicate 'singla-asn1-type', i.e. a constructed type. So since that information is already lost before we ever get the record from the Erlang asn1 decoder, it will be re-encoded as OCTET STRING :( Until this is fixed in the asn1ct/asn1rt code, we have to use this workaround...
-rw-r--r--src/map_codec.erl24
-rw-r--r--test/map_codec_tests.erl9
2 files changed, 27 insertions, 6 deletions
diff --git a/src/map_codec.erl b/src/map_codec.erl
index 3922d28..21e2c41 100644
--- a/src/map_codec.erl
+++ b/src/map_codec.erl
@@ -19,7 +19,7 @@
-module(map_codec).
-author('Harald Welte <laforge@gnumonks.org>').
-%-include("map.hrl").
+-include("map.hrl").
-include_lib("osmo_ss7/include/isup.hrl").
-export([parse_tcap_msg/1, encode_tcap_msg/1]).
@@ -117,11 +117,31 @@ parse_tcap_msg(MsgBin) when is_binary(MsgBin) ->
parse_tcap_msg(Msg) when is_list(Msg) ->
case asn1rt:decode('map', 'MapSpecificPDUs', Msg) of
{ok, {Type, TcapMsgDec}} ->
- {Type, TcapMsgDec};
+ fixup_dialogue({Type, TcapMsgDec});
Error ->
Error
end.
+% Extract the dialoguePortion and feed it through external_1990ify/1
+fixup_dialogue({'begin', Beg = #'MapSpecificPDUs_begin'{dialoguePortion=Dia}}) ->
+ {'begin', Beg#'MapSpecificPDUs_begin'{dialoguePortion = external_1990ify(Dia)}};
+fixup_dialogue({'end', Beg = #'MapSpecificPDUs_end'{dialoguePortion=Dia}}) ->
+ {'end', Beg#'MapSpecificPDUs_end'{dialoguePortion = external_1990ify(Dia)}};
+fixup_dialogue({'continue', Beg = #'MapSpecificPDUs_continue'{dialoguePortion=Dia}}) ->
+ {'continue', Beg#'MapSpecificPDUs_continue'{dialoguePortion = external_1990ify(Dia)}};
+fixup_dialogue({'unidirectional', Beg = #'MapSpecificPDUs_unidirectional'{dialoguePortion=Dia}}) ->
+ {'unidirectional', Beg#'MapSpecificPDUs_unidirectional'{dialoguePortion = external_1990ify(Dia)}};
+fixup_dialogue(Default) ->
+ Default.
+
+% Take the EXTERNAL date type and convert from 1994-style to 1990 with 'single-ASN1-type'
+external_1990ify({'EXTERNAL', {syntax, DirRef}, IndirRef, Data}) when is_list(Data); is_binary(Data) ->
+ #'EXTERNAL'{'direct-reference' = DirRef,
+ 'indirect-reference' = IndirRef,
+ encoding = {'single-ASN1-type', Data}};
+external_1990ify(Default) ->
+ Default.
+
encode_tcap_msg({Type, TcapMsgDec}) ->
case asn1rt:encode('map', 'MapSpecificPDUs', {Type, TcapMsgDec}) of
{ok, List} ->
diff --git a/test/map_codec_tests.erl b/test/map_codec_tests.erl
index 00ff546..505549b 100644
--- a/test/map_codec_tests.erl
+++ b/test/map_codec_tests.erl
@@ -26,13 +26,12 @@
-define(_assertEqualArgs(Expect, Expr, Args), ?_test(?assertEqual(Expect, Expr, Args))).
-define(TCAP_MSG_BIN, <<100,65,73,4,81,1,2,200,107,42,40,40,6,7,0,17,134,5,1,1,1,160,29,97,27,128,2,7,128,161,9,6,7,4,0,0,1,0,1,3,162,3,2,1,0,163,5,161,3,2,1,0,108,13,163,11,2,1,64,2,1,8,48,3,10,1,0>>).
--define(TCAP_MSG_DEC, {'end',{'MapSpecificPDUs_end',[81,1,2,200],{'EXTERNAL',{syntax,{0,0,17,773,1,1,1}},asn1_NOVALUE,[97,27,128,2,7,128,161,9,6,7,4,0,0,1,0,1,3,162,3,2,1,0,163,5,161,3,2,1,0]},[{basicROS,{returnError,{'MapSpecificPDUs_end_components_SEQOF_basicROS_returnError',{present,64},{local,8},{'RoamingNotAllowedParam',plmnRoamingNotAllowed,asn1_NOVALUE,asn1_NOVALUE}}}}]}}).
+-define(TCAP_MSG_DEC, {'end',{'MapSpecificPDUs_end',[81,1,2,200],{'EXTERNAL',{0,0,17,773,1,1,1},asn1_NOVALUE,asn1_NOVALUE, {'single-ASN1-type', [97,27,128,2,7,128,161,9,6,7,4,0,0,1,0,1,3,162,3,2,1,0,163,5,161,3,2,1,0]}},[{basicROS,{returnError,{'MapSpecificPDUs_end_components_SEQOF_basicROS_returnError',{present,64},{local,8},{'RoamingNotAllowedParam',plmnRoamingNotAllowed,asn1_NOVALUE,asn1_NOVALUE}}}}]}}).
parse_test() ->
?assertEqual(?TCAP_MSG_DEC, map_codec:parse_tcap_msg(?TCAP_MSG_BIN)).
-% BER allows for different binary encodings of each message, the test below is not valid
-%encode_test() ->
-% ?assertEqual(?TCAP_MSG_BIN, map_codec:encode_tcap_msg(?TCAP_MSG_DEC)).
+encode_test() ->
+ ?assertEqual(?TCAP_MSG_BIN, map_codec:encode_tcap_msg(?TCAP_MSG_DEC)).
-define(ADDR_DEC, #party_number{nature_of_addr_ind = ?ISUP_ADDR_NAT_INTERNATIONAL,
internal_net_num = undefined,
@@ -109,12 +108,14 @@ handle_sccp(S = #sccp_msg{msg_type = ?SCCP_MSGT_UDT, parameters = Params}, Path)
?debugFmt("Path: ~p~nMAP Decode Error: ~w~n", [PathOut, ErrTuple]),
erlang:error(ErrTuple);
MapDec ->
+ %?debugFmt("~w~n", [MapDec]),
case map_codec:encode_tcap_msg(MapDec) of
{error, Error} ->
ErrTuple = {Error, erlang:get_stacktrace(), [{map_dec, MapDec}]},
?debugFmt("Path: ~p~nMAP Encode Error: ~w~n", [PathOut, ErrTuple]),
erlang:error(ErrTuple);
MapReenc ->
+ %?assertEqualArgs(UserData, MapReenc, [{layer, map}, {path, Path}]),
MapReencDec = map_codec:parse_tcap_msg(MapReenc),
?assertEqualArgs(MapDec, MapReencDec, [{layer, map}, {path, Path}])
end