File 2428-PER-Slightly-improve-error-reporting-for-encoding.patch of Package erlang

From 2a206d87470fc61656dcfc67e428fd61cb8ee39c Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Wed, 15 Feb 2017 14:04:25 +0100
Subject: [PATCH 1/4] PER: Slightly improve error reporting for encoding

Generate slightly better error reasons when encoding of INTEGER,
ENUMERATED, or BOOLEAN fails.
---
 lib/asn1/src/asn1ct_imm.erl             | 11 ++++----
 lib/asn1/src/asn1rtt_per_common.erl     |  2 ++
 lib/asn1/test/asn1_SUITE_data/Prim.asn1 |  2 ++
 lib/asn1/test/testPrim.erl              | 46 +++++++++++++++++++++------------
 4 files changed, 40 insertions(+), 21 deletions(-)

diff --git a/lib/asn1/src/asn1ct_imm.erl b/lib/asn1/src/asn1ct_imm.erl
index 2ab848652..1e15748e3 100644
--- a/lib/asn1/src/asn1ct_imm.erl
+++ b/lib/asn1/src/asn1ct_imm.erl
@@ -216,7 +216,8 @@ per_enc_legacy_bit_string(Val0, NNL0, Constraint0, Aligned) ->
 per_enc_boolean(Val0, _Aligned) ->
     {B,[Val]} = mk_vars(Val0, []),
     B++build_cond([[{eq,Val,false},{put_bits,0,1,[1]}],
-		   [{eq,Val,true},{put_bits,1,1,[1]}]]).
+		   [{eq,Val,true},{put_bits,1,1,[1]}],
+                   ['_',{error,{illegal_boolean,Val}}]]).
 
 per_enc_choice(Val0, Cs0, _Aligned) ->
     {B,[Val]} = mk_vars(Val0, []),
@@ -237,7 +238,7 @@ per_enc_enumerated(Val0, Root, Aligned) ->
     B++[{'cond',Cs++enumerated_error(Val)}].
 
 enumerated_error(Val) ->
-    [['_',{error,Val}]].
+    [['_',{error,{illegal_enumerated,Val}}]].
 
 per_enc_integer(Val0, Constraint0, Aligned) ->
     {B,[Val]} = mk_vars(Val0, []),
@@ -1107,7 +1108,7 @@ per_enc_integer_1(Val0, [{{_,_}=Constr,[]}], Aligned) ->
 per_enc_integer_1(Val0, [Constr], Aligned) ->
     {Prefix,Check,Action} = per_enc_integer_2(Val0, Constr, Aligned),
     Prefix++build_cond([[Check|Action],
-			['_',{error,Val0}]]).
+			['_',{error,{illegal_integer,Val0}}]]).
 
 per_enc_integer_2(Val, {'SingleValue',Sv}, Aligned) when is_integer(Sv) ->
     per_enc_constrained(Val, Sv, Sv, Aligned);
@@ -2353,9 +2354,9 @@ enc_cg({'cond',Cs}) ->
     enc_cg_cond(Cs);
 enc_cg({error,Error}) when is_function(Error, 0) ->
     Error();
-enc_cg({error,Var0}) ->
+enc_cg({error,{Tag,Var0}}) ->
     Var = mk_val(Var0),
-    emit(["exit({error,{asn1,{illegal_value,",Var,"}}})"]);
+    emit(["exit({error,{asn1,{",Tag,",",Var,"}}})"]);
 enc_cg({integer,Int}) ->
     emit(mk_val(Int));
 enc_cg({lc,Body,Var,List}) ->
diff --git a/lib/asn1/src/asn1rtt_per_common.erl b/lib/asn1/src/asn1rtt_per_common.erl
index 3896cb7fa..e7edfb1ee 100644
--- a/lib/asn1/src/asn1rtt_per_common.erl
+++ b/lib/asn1/src/asn1rtt_per_common.erl
@@ -140,6 +140,8 @@ encode_relative_oid(Val) when is_tuple(Val) ->
 encode_relative_oid(Val) when is_list(Val) ->
     list_to_binary([e_object_element(X)||X <- Val]).
 
+encode_unconstrained_number(Val) when not is_integer(Val) ->
+    exit({error,{asn1,{illegal_integer,Val}}});
 encode_unconstrained_number(Val) when Val >= 0 ->
     if
 	Val < 16#80 ->
diff --git a/lib/asn1/test/asn1_SUITE_data/Prim.asn1 b/lib/asn1/test/asn1_SUITE_data/Prim.asn1
index 4fe090168..91c8696e6 100644
--- a/lib/asn1/test/asn1_SUITE_data/Prim.asn1
+++ b/lib/asn1/test/asn1_SUITE_data/Prim.asn1
@@ -18,6 +18,8 @@ BEGIN
   IntExpPri ::=  [PRIVATE 51] EXPLICIT INTEGER
   IntExpApp ::=  [APPLICATION 52] EXPLICIT INTEGER
 
+  IntConstrained ::= INTEGER (0..255)
+
   IntEnum ::=  INTEGER {first(1),last(31)}
 
   Enum ::=  ENUMERATED {monday(1),tuesday(2),wednesday(3),thursday(4),
diff --git a/lib/asn1/test/testPrim.erl b/lib/asn1/test/testPrim.erl
index 96a2dd6c7..14546ff41 100644
--- a/lib/asn1/test/testPrim.erl
+++ b/lib/asn1/test/testPrim.erl
@@ -34,15 +34,12 @@ bool(Rules) ->
     Types = ['Bool','BoolCon','BoolPri','BoolApp',
 	     'BoolExpCon','BoolExpPri','BoolExpApp'],
     [roundtrip(T, V) || T <- Types, V <- [true,false]],
-    case Rules of
-	ber ->
-	    [begin
-		 {error,{asn1,{encode_boolean,517}}} = enc_error(T, 517)
-	     end || T <- Types],
-	    ok;
-	_ ->
-	    ok
-    end.
+    Tag = case Rules of
+              ber -> encode_boolean;
+              _ -> illegal_boolean
+          end,
+    [{Tag,517} = enc_error(T, 517) || T <- Types],
+    ok.
 
 
 int(Rules) ->
@@ -60,10 +57,22 @@ int(Rules) ->
 	      123456789,12345678901234567890,
 	      -1,-2,-3,-4,-100,-127,-255,-256,-257,
 	      -1234567890,-2147483648],
-    [roundtrip(T, V) ||
-	T <- ['Int','IntCon','IntPri','IntApp',
-	      'IntExpCon','IntExpPri','IntExpApp'],
-	V <- [1|Values]],
+    Types = ['Int','IntCon','IntPri','IntApp',
+             'IntExpCon','IntExpPri','IntExpApp'],
+    _ = [roundtrip(T, V) || T <- Types, V <- [1|Values]],
+    Tag = case Rules of
+              ber -> encode_integer;
+              _ -> illegal_integer
+          end,
+    _ = [{Tag,V} = enc_error(T, V) ||
+            T <- Types, V <- [atom,42.0,{a,b,c}]],
+    case Rules of
+        ber ->
+            ok;
+        _ ->
+            _ = [{Tag,V} = enc_error('IntConstrained', V) ||
+                    V <- [atom,-1,256,42.0]]
+    end,
 
     %%==========================================================
     %% IntEnum ::=  INTEGER {first(1),last(31)} 
@@ -119,7 +128,11 @@ enum(Rules) ->
 
     roundtrip('Enum', monday),
     roundtrip('Enum', thursday),
-    {error,{asn1,{_,4}}} = enc_error('Enum', 4),
+    Tag = case Rules of
+              ber -> enumerated_not_in_range;
+              _ -> illegal_enumerated
+          end,
+    {Tag,4} = enc_error('Enum', 4),
 
     case Rules of
 	Per when Per =:= per; Per =:= uper ->
@@ -182,13 +195,14 @@ roundtrip(Type, Value, ExpectedValue) ->
 enc_error(T, V) ->
     case get(no_ok_wrapper) of
 	false ->
-	    'Prim':encode(T, V);
+	    {error,{asn1,Reason}} = 'Prim':encode(T, V),
+            Reason;
 	true ->
 	    try 'Prim':encode(T, V) of
 		_ ->
 		    ?t:fail()
 	    catch
-		_:Reason ->
+		_:{error,{asn1,Reason}} ->
 		    Reason
 	    end
     end.
-- 
2.12.0

openSUSE Build Service is sponsored by