File 2406-Clean-up-handling-of-textual-order.patch of Package erlang

From 75f9ee5823d57bfb60febc7371920a6858c895fd Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Fri, 13 Jan 2017 14:27:59 +0100
Subject: [PATCH 06/14] Clean up handling of textual order

The to_encoding_order/1 function can be eliminated if we
incorporate its functionality into textual_order/2.

textual_order/2 has a workaround for TermList being longer
than OrderList. Remove the workaround, because the code
being generated would certainly be wrong (better let the compiler
crash and receive a bug report if it happens). The workaround
was not necessary to successfully compile the entire Erlang/OTP
and to run the asn1 test suite.
---
 lib/asn1/src/asn1ct_constructed_per.erl | 26 +++++++++-----------------
 1 file changed, 9 insertions(+), 17 deletions(-)

diff --git a/lib/asn1/src/asn1ct_constructed_per.erl b/lib/asn1/src/asn1ct_constructed_per.erl
index a3a0d4c3c..e9cfc56fa 100644
--- a/lib/asn1/src/asn1ct_constructed_per.erl
+++ b/lib/asn1/src/asn1ct_constructed_per.erl
@@ -350,7 +350,7 @@ gen_dec_pack(Typename, CompList) ->
 	    %% CompList is used here because we don't want
 	    %% ExtensionAdditionGroups to be wrapped in SEQUENCES when
 	    %% we are ordering the fields according to textual order
-	    mkvlist(textual_order(to_encoding_order(CompList),asn1ct_name:all(term))),
+	    mkvlist(textual_order(CompList, asn1ct_name:all(term))),
 	    emit("},")
     end,
     emit({{curr,bytes},"}"}).
@@ -378,17 +378,16 @@ filter_ext_add_groups([H|T], Acc) ->
     filter_ext_add_groups(T, [H|Acc]);
 filter_ext_add_groups([], Acc) -> Acc.
 
-textual_order([#'ComponentType'{textual_order=undefined}|_],TermList) ->
+textual_order([#'ComponentType'{textual_order=undefined}|_], TermList) ->
     TermList;
-textual_order(CompList,TermList) when is_list(CompList) ->
+textual_order(CompList, TermList) when is_list(CompList) ->
     OrderList = [Ix||#'ComponentType'{textual_order=Ix} <- CompList],
-    [Term||{_,Term}<-
-	       lists:sort(lists:zip(OrderList,
-				    lists:sublist(TermList,length(OrderList))))];
-	       %% sublist is just because Termlist can sometimes be longer than
-	       %% OrderList, which it really shouldn't
-textual_order({Root,Ext},TermList) ->
-    textual_order(Root ++ Ext,TermList).
+    Zipped = lists:sort(lists:zip(OrderList, TermList)),
+    [Term || {_,Term} <- Zipped];
+textual_order({Root,Ext}, TermList) ->
+    textual_order(Root ++ Ext, TermList);
+textual_order({R1,Ext,R2}, TermList) ->
+    textual_order(R1 ++ R2 ++ Ext, TermList).
 
 to_textual_order({Root,Ext}) ->
     {to_textual_order(Root),Ext};
@@ -778,13 +777,6 @@ get_optionality_pos(TextPos,OptTable) ->
 	    no_num
     end.
 
-to_encoding_order(Cs) when is_list(Cs) ->
-    Cs;
-to_encoding_order(Cs = {_Root,_Ext}) ->
-    Cs;
-to_encoding_order({R1,Ext,R2}) ->
-    {R1++R2,Ext}.
-
 add_textual_order(Cs) when is_list(Cs) ->
     {NewCs,_} = add_textual_order1(Cs,1),
     NewCs;
-- 
2.11.1

openSUSE Build Service is sponsored by