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...
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 @@
 		?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