File 2429-PER-encoding-Emit-comments-about-each-attribute.patch of Package erlang

From d5c350d57b92272b344a4aa29873ea9f7980ce7b Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Thu, 16 Feb 2017 07:09:02 +0100
Subject: [PATCH 2/4] PER encoding: Emit comments about each attribute

To make it easier to find your way in the generated code,
add a comment about each attribute in the generated code
for SEQUENCE and SET.
---
 lib/asn1/src/asn1ct_constructed_per.erl | 35 ++++++++++++++++++---------------
 lib/asn1/src/asn1ct_imm.erl             | 16 ++++++++++++++-
 2 files changed, 34 insertions(+), 17 deletions(-)

diff --git a/lib/asn1/src/asn1ct_constructed_per.erl b/lib/asn1/src/asn1ct_constructed_per.erl
index b7579c806..9cd9864b8 100644
--- a/lib/asn1/src/asn1ct_constructed_per.erl
+++ b/lib/asn1/src/asn1ct_constructed_per.erl
@@ -979,6 +979,10 @@ mark_optional(Other) ->
 gen_enc_components_call1(Gen, TopType, [C|Rest], DynamicEnc, Ext) ->
     #'ComponentType'{name=Cname,typespec=Type,
                      prop=Prop,textual_order=Num} = C,
+    InnerType = asn1ct_gen:get_inner(Type#type.def),
+    CommentString = attribute_comment(InnerType, Num, Cname),
+    ImmComment = asn1ct_imm:enc_comment(CommentString),
+
     {Imm0,Element} = enc_fetch_field(Gen, Num, Prop),
     Imm1 = gen_enc_line_imm(Gen, TopType, Cname, Type,
                             Element, DynamicEnc, Ext),
@@ -993,7 +997,7 @@ gen_enc_components_call1(Gen, TopType, [C|Rest], DynamicEnc, Ext) ->
 	   end,
     Imm = case Imm2 of
 	      [] -> [];
-	      _ -> Imm0 ++ Imm2
+	      _ -> [ImmComment|Imm0 ++ Imm2]
 	  end,
     [Imm|gen_enc_components_call1(Gen, TopType, Rest, DynamicEnc, Ext)];
 gen_enc_components_call1(_Gen, _TopType, [], _, _) ->
@@ -1328,27 +1332,17 @@ gen_dec_comp_calls([], _, _, _, _, _, _, Tpos, Acc) ->
 
 gen_dec_comp_call(Comp, Gen, TopType, Tpos, OptTable, DecInfObj,
 		  Ext, NumberOfOptionals) ->
-    #'ComponentType'{typespec=Type,prop=Prop,textual_order=TextPos} = Comp,
+    #'ComponentType'{name=Cname,typespec=Type,
+                     prop=Prop,textual_order=TextPos} = Comp,
     Pos = case Ext of
 	      noext -> Tpos;
 	      {ext,Epos,_Enum} -> Tpos - Epos + 1
 	  end,
-    InnerType = 
-	case Type#type.def of
-	    #'ObjectClassFieldType'{type=InType} ->
-		InType;
-	    Def ->
-		asn1ct_gen:get_inner(Def)
-	end,
+    InnerType = asn1ct_gen:get_inner(Type#type.def),
 
-    DispType = case InnerType of
-		   #'Externaltypereference'{type=T} -> T;
-		   IT when is_tuple(IT) -> element(2,IT);
-		   _ -> InnerType
-	       end,
+    CommentString = attribute_comment(InnerType, TextPos, Cname),
     Comment = fun(St) ->
-		      emit([nl,"%% attribute number ",TextPos,
-			    " with type ",DispType,nl]),
+		      emit([nl,"%% ",CommentString,nl]),
 		      St
 	      end,
 
@@ -1987,3 +1981,12 @@ enc_dig_out_value(#gen{pack=map}=Gen, [{_,Name}|T], Value) ->
 
 make_var(Base) ->
     {var,atom_to_list(asn1ct_gen:mk_var(asn1ct_name:curr(Base)))}.
+
+attribute_comment(InnerType, TextPos, Cname) ->
+    DispType = case InnerType of
+		   #'Externaltypereference'{type=T} -> T;
+		   IT when is_tuple(IT) -> element(2,IT);
+		   _ -> InnerType
+	       end,
+    Comment = ["attribute ",Cname,"(",TextPos,") with type ",DispType],
+    lists:concat(Comment).
diff --git a/lib/asn1/src/asn1ct_imm.erl b/lib/asn1/src/asn1ct_imm.erl
index 1e15748e3..754451b27 100644
--- a/lib/asn1/src/asn1ct_imm.erl
+++ b/lib/asn1/src/asn1ct_imm.erl
@@ -41,7 +41,8 @@
          per_enc_extensions_map/4,
          per_enc_optional/2]).
 -export([per_enc_sof/5]).
--export([enc_absent/3,enc_append/1,enc_element/2,enc_maps_get/2]).
+-export([enc_absent/3,enc_append/1,enc_element/2,enc_maps_get/2,
+         enc_comment/1]).
 -export([enc_cg/2]).
 -export([optimize_alignment/1,optimize_alignment/2,
 	 dec_slim_cg/2,dec_code_gen/2]).
@@ -438,6 +439,9 @@ enc_maps_get(N, Val0) ->
     {var,SrcVar} = Val,
     {[{assign,DstExpr,SrcVar}],Dst0}.
 
+enc_comment(Comment) ->
+    {comment,Comment}.
+
 enc_cg(Imm0, false) ->
     Imm1 = enc_cse(Imm0),
     Imm2 = enc_pre_cg(Imm1),
@@ -1052,6 +1056,7 @@ split_off_nonbuilding(Imm) ->
 
 is_nonbuilding({assign,_,_}) -> true;
 is_nonbuilding({call,_,_,_,_}) -> true;
+is_nonbuilding({comment,_}) -> true;
 is_nonbuilding({lc,_,_,_,_}) -> true;
 is_nonbuilding({set,_,_}) -> true;
 is_nonbuilding({list,_,_}) -> true;
@@ -1932,6 +1937,8 @@ enc_opt({'cond',Cs0}, St0) ->
 	    {Cs,Type} = enc_opt_cond_1(Cs1, Type0, [{Cond,Imm}]),
 	    {{'cond',Cs},St0#ost{t=Type}}
     end;
+enc_opt({comment,_}=Imm, St) ->
+    {Imm,St#ost{t=undefined}};
 enc_opt({cons,H0,T0}, St0) ->
     {H,#ost{t=TypeH}=St1} = enc_opt(H0, St0),
     {T,#ost{t=TypeT}=St} = enc_opt(T0, St1),
@@ -2321,6 +2328,9 @@ enc_cg({block,Imm}) ->
     enc_cg(Imm),
     emit([nl,
 	  "end"]);
+enc_cg({seq,{comment,Comment},Then}) ->
+    emit(["%% ",Comment,nl]),
+    enc_cg(Then);
 enc_cg({seq,First,Then}) ->
     enc_cg(First),
     emit([com,nl]),
@@ -2619,6 +2629,8 @@ enc_opt_al({call,per_common,encode_unconstrained_number,[_]}=Call, _) ->
     {[Call],0};
 enc_opt_al({call,_,_,_,_}=Call, Al) ->
     {[Call],Al};
+enc_opt_al({comment,_}=Imm, Al) ->
+    {[Imm],Al};
 enc_opt_al({'cond',Cs0}, Al0) ->
     {Cs,Al} = enc_opt_al_cond(Cs0, Al0),
     {[{'cond',Cs}],Al};
@@ -2715,6 +2727,8 @@ per_fixup([{block,Block}|T]) ->
     [{block,per_fixup(Block)}|per_fixup(T)];
 per_fixup([{'assign',_,_}=H|T]) ->
     [H|per_fixup(T)];
+per_fixup([{comment,_}=H|T]) ->
+    [H|per_fixup(T)];
 per_fixup([{'cond',Cs0}|T]) ->
     Cs = [[C|per_fixup(Act)] || [C|Act] <- Cs0],
     [{'cond',Cs}|per_fixup(T)];
-- 
2.12.0

openSUSE Build Service is sponsored by