File 8522-asn1-Retain-the-definition-order-in-the-JER-encoding.patch of Package erlang

From 92bb6cb3a7d7edfe36db2b06930ec54037c5161d Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Mon, 6 May 2024 08:42:27 +0200
Subject: [PATCH] asn1: Retain the definition order in the JER encoding

Consider this ASN.1 module:

    TT DEFINITIONS AUTOMATIC TAGS ::=
    BEGIN
       S1 ::= SEQUENCE {
         nisse INTEGER,
         arne INTEGER,
         kalle INTEGER,
         fredrik INTEGER
       }
    END

When encoding the `S1` SEQUENCE to JER (JSON encoding rules) using one
of the pre-releases of Erlang/OTP 27 that includes the new `json`
module, the order of the keys and value in the definition of `S1`
would not be retained:

    1> asn1ct:compile('TT', [jer]).
    ok
    2> io:format("~ts\n", [element(2, 'TT':encode('S1', {'S1',1,2,3,4}))]).
    {"arne":2,"fredrik":4,"kalle":3,"nisse":1}
    ok

While technically not a bug, because the order is not documented, it
is a change from how Erlang/OTP 26 and earlier did the JSON encoding,
and some use cases that depended on that order could break.
Also, it can be helpful for debugging to keep the order.

Therefore, this commit ensures that the order is retained:

    1> asn1ct:compile('TT', [jer]).
    ok
    2> io:format("~ts\n", [element(2, 'TT':encode('S1', {'S1',1,2,3,4}))]).
    {"nisse":1,"arne":2,"kalle":3,"fredrik":4}
    ok

Closes #8453
---
 lib/asn1/src/asn1rtt_jer.erl | 12 +++++++++---
 1 file changed, 9 insertions(+), 3 deletions(-)

diff --git a/lib/asn1/src/asn1rtt_jer.erl b/lib/asn1/src/asn1rtt_jer.erl
index 4744ae0df0..8361116f6c 100644
--- a/lib/asn1/src/asn1rtt_jer.erl
+++ b/lib/asn1/src/asn1rtt_jer.erl
@@ -34,7 +34,12 @@
 encode_jer(Module, Type, Val) ->
     Info = Module:typeinfo(Type),
     Enc = encode_jer(Info, Val),
-    iolist_to_binary(json:encode(Enc)).
+    EncFun = fun({'KV_LIST', Value}, Encode) ->
+                     json:encode_key_value_list(Value, Encode);
+                (Other, Encode) ->
+                     json:encode_value(Other, Encode)
+             end,
+    iolist_to_binary(json:encode(Enc, EncFun)).
 
 %% {sequence,
 %%    Name::atom() % The record name used for the sequence 
@@ -183,7 +188,7 @@ encode_jer_component_map([{_Name, _AName, _Type, 'OPTIONAL'} | CompInfos], MapVa
 encode_jer_component_map([{_Name, _AName, _Type, {'DEFAULT',_}} | CompInfos], MapVal, Acc) ->
     encode_jer_component_map(CompInfos, MapVal, Acc);
 encode_jer_component_map([], MapVal, Acc) when map_size(MapVal) =:= length(Acc) ->
-    maps:from_list(Acc);
+    {'KV_LIST', lists:reverse(Acc)};
 encode_jer_component_map(_, MapVal, Acc) ->
     ErroneousKeys = maps:keys(MapVal) -- [K || {K,_V} <- Acc],
     exit({error,{asn1,{{encode,'SEQUENCE'},{erroneous_keys,ErroneousKeys}}}}).
@@ -196,7 +201,8 @@ encode_jer_component([{Name, Type, _OptOrDefault} | CompInfos], [Value | Rest],
     Enc = encode_jer(Type, Value),
     encode_jer_component(CompInfos, Rest, [{Name,Enc}|Acc]);
 encode_jer_component([], _, Acc) ->
-    maps:from_list(Acc).
+    {'KV_LIST', lists:reverse(Acc)}.
+
 
 decode_jer(Module, Type, Val) ->
     TypeInfo = Module:typeinfo(Type),
-- 
2.35.3

openSUSE Build Service is sponsored by