File 2911-Add-JER-backend.patch of Package erlang

From 3d679b69c47d282419ae07cbf34873c070de289a Mon Sep 17 00:00:00 2001
From: Kenneth Lundin <kenneth.lundin@ericsson.com>
Date: Fri, 23 Aug 2019 09:44:53 +0200
Subject: [PATCH] Add JER backend

---
 lib/asn1/doc/src/asn1_getting_started.xml          |  12 +-
 lib/asn1/doc/src/asn1ct.xml                        |  42 +-
 lib/asn1/src/Makefile                              |   2 +
 lib/asn1/src/asn1_records.hrl                      |   3 +-
 lib/asn1/src/asn1ct.erl                            |   5 +-
 lib/asn1/src/asn1ct_gen.erl                        | 156 +++++-
 lib/asn1/src/asn1ct_gen_jer.erl                    | 605 +++++++++++++++++++++
 lib/asn1/src/asn1ct_value.erl                      |  19 +-
 lib/asn1/src/asn1rtt_jer.erl                       | 501 +++++++++++++++++
 lib/asn1/test/asn1_SUITE.erl                       |  28 +-
 lib/asn1/test/asn1_SUITE_data/InfClass.asn         |   6 +-
 .../asn1_SUITE_data/extensionAdditionGroup.erl     |   3 +-
 lib/asn1/test/asn1_app_SUITE.erl                   |   2 +-
 lib/asn1/test/asn1_test_lib.erl                    |   2 +-
 lib/asn1/test/testChoPrim.erl                      |   8 +-
 lib/asn1/test/testCompactBitString.erl             |  11 +-
 lib/asn1/test/testConstraints.erl                  |  13 +-
 lib/asn1/test/testContextSwitchingTypes.erl        |   5 +-
 lib/asn1/test/testDeepTConstr.erl                  |   1 +
 lib/asn1/test/testEnumExt.erl                      |  17 +-
 lib/asn1/test/testExtensibilityImplied.erl         |  11 +-
 lib/asn1/test/testExtensionDefault.erl             |  13 +-
 lib/asn1/test/testFragmented.erl                   |   1 +
 lib/asn1/test/testINSTANCE_OF.erl                  |  20 +-
 lib/asn1/test/testImporting.erl                    |  11 +-
 lib/asn1/test/testInfObj.erl                       | 293 +++++-----
 lib/asn1/test/testInfObjExtract.erl                |   5 +-
 lib/asn1/test/testInfObjectClass.erl               |  41 +-
 lib/asn1/test/testMergeCompile.erl                 |   1 +
 lib/asn1/test/testOpenTypeImplicitTag.erl          |   6 +
 lib/asn1/test/testPrim.erl                         |  56 +-
 lib/asn1/test/testTCAP.erl                         |   1 +
 lib/asn1/test/testUniqueObjectSets.erl             |   1 +
 33 files changed, 1645 insertions(+), 256 deletions(-)
 create mode 100644 lib/asn1/src/asn1ct_gen_jer.erl
 create mode 100644 lib/asn1/src/asn1rtt_jer.erl

diff --git a/lib/asn1/doc/src/asn1_getting_started.xml b/lib/asn1/doc/src/asn1_getting_started.xml
index 907bf051d5..69d2b93356 100644
--- a/lib/asn1/doc/src/asn1_getting_started.xml
+++ b/lib/asn1/doc/src/asn1_getting_started.xml
@@ -165,7 +165,7 @@ erlc -bber ../Example.asn
 erlc -o ../asnfiles -I ../asnfiles -I /usr/local/standards/asn1 Person.asn</pre>
       <p>Useful options for the ASN.1 compiler:</p>
       <taglist>
-        <tag><c>-b[ber | per | uper]</c></tag>
+        <tag><c>-b[ber | per | uper | jer]</c></tag>
         <item>
           <p>Choice of encoding rules. If omitted, <c>ber</c> is the
           default.</p>
@@ -185,7 +185,15 @@ erlc -o ../asnfiles -I ../asnfiles -I /usr/local/standards/asn1 Person.asn</pre>
         </item>
         <tag><c>+der</c></tag>
         <item>
-          <p>DER encoding rule. Only when using option <c>-ber</c>.</p>
+          <p>DER encoding rule. Only when using option <c>-bber</c>.</p>
+        </item>
+        <tag><c>+jer</c></tag>
+        <item>
+          <p>Functions <c>jer_encode/2</c> and <c>jer_decode/2</c> for
+	  JSON encoding rules are generated together with functions for
+	  <c>ber</c> or <c>per</c>. Only to be used when the main encoding
+	  option is <c>-bber</c>, <c>-bper</c> or <c>-buper</c> 
+	  </p>
         </item>
         <tag><c>+maps</c></tag>
         <item>
diff --git a/lib/asn1/doc/src/asn1ct.xml b/lib/asn1/doc/src/asn1ct.xml
index eb67222c30..585c4c1031 100644
--- a/lib/asn1/doc/src/asn1ct.xml
+++ b/lib/asn1/doc/src/asn1ct.xml
@@ -58,7 +58,8 @@
 
       <note>
 	<p>In OTP R16, the options were simplified. The back end is chosen
-	using one of the options <c>ber</c>, <c>per</c>, or <c>uper</c>.
+	using one of the options <c>ber</c>, <c>per</c>, <c>uper</c> or
+	<c>jer</c>.
 	Options <c>optimize</c>, <c>nif</c>, and <c>driver</c> options
 	are no longer necessary (and the ASN.1 compiler generates a
 	warning if they are used). Options <c>ber_bin</c>, <c>per_bin</c>,
@@ -78,7 +79,7 @@
       <type>
         <v>Asn1module = atom() | string()</v>
         <v>Options = [Option| OldOption]</v>
-        <v>Option = ber | per | uper | der | compact_bit_string |
+        <v>Option = ber | per | uper | jer | der | compact_bit_string |
 	legacy_bit_string | legacy_erlang_types |
 	noobj | {n2n, EnumTypeName} |{outdir, Dir} | {i, IncludeDir} |
 	asn1config | undec_rest | no_ok_wrapper |
@@ -142,12 +143,41 @@ File3.asn</pre>
 	  available options are as follows:
 	</p>
 	<taglist>
-          <tag><c>ber | per | uper</c></tag>
+          <tag><c>ber | per | uper | jer</c></tag>
           <item>
             <p>
 	      The encoding rule to be used. The supported encoding rules
-	      are Basic Encoding Rules (BER),
-	      Packed Encoding Rules (PER) aligned, and PER unaligned.
+	      are Basic Encoding Rules (<c>ber</c>),
+	      Packed Encoding Rules (<c>per</c>) aligned, PER unaligned (<c>uper</c>) and
+	      JSON Encoding Rules (<c>jer</c>).
+	      The <c>jer</c> option can be used by itself to generate a module
+	      that only supports encoding/decoding to JER or it can
+	      be used as a supplementary option to ber, per and uper.
+	      In the latter case a module with for both the main encoding rules
+	      and JER will be generated.
+	      The exported functions for JER will then be
+	      <c>jer_encode(Type, Value)</c> and <c>jer_decode(Type, Bytes)</c>.
+	    </p>
+	    <p>
+	      The <c>jer</c> encoding rules (ITU-T X.697) are experimental in
+	      OTP 22.
+	      There is support for a subset of the X.697 standard, for example there is no support for:
+	    </p>
+	    <list>
+	      <item>JER encoding instructions</item>
+	      <item>the REAL type</item>
+	    </list>
+	    <p>
+	      Also note that when using the <c>jer</c> encoding rules the
+	      generated module will get a dependency to an external json
+	      component. The generated code is currently tested together with:
+	    </p>
+	    <list>
+	      <item><c>jsx</c> which currently is the default.</item>
+	      <item><c>jsone</c> can be chosen instead of <c>jsx</c>
+	      by providing the option <c>{d,jsone}</c>.</item>
+	    </list>
+	    <p>
 	      If the encoding rule option is omitted, <c>ber</c> 
 	      is the default.
 	    </p>
@@ -160,7 +190,7 @@ File3.asn</pre>
           <tag><c>der</c></tag>
           <item>
             <p>
-	      With this option the Distinguished Encoding Rules (DER) is chosen.
+	      With this option the Distinguished Encoding Rules (<c>der</c>) is chosen.
 	      DER is regarded as a specialized variant of the BER encoding 
               rule. Therefore, this option only makes sense together
 	      with option <c>ber</c>.
diff --git a/lib/asn1/src/Makefile b/lib/asn1/src/Makefile
index 1c3bdfcaa8..a6ff72898c 100644
--- a/lib/asn1/src/Makefile
+++ b/lib/asn1/src/Makefile
@@ -59,6 +59,7 @@ CT_MODULES= \
 	asn1ct_constructed_per \
 	asn1ct_constructed_ber_bin_v2 \
 	asn1ct_gen_ber_bin_v2 \
+	asn1ct_gen_jer \
 	asn1ct_imm \
 	asn1ct_rtt \
 	asn1ct_value \
@@ -173,6 +174,7 @@ RT_TEMPLATES = asn1rtt_check \
 	       asn1rtt_per_common \
                asn1rtt_real_common \
 	       asn1rtt_ber \
+               asn1rtt_jer \
 	       asn1rtt_per \
 	       asn1rtt_uper
 
diff --git a/lib/asn1/src/asn1_records.hrl b/lib/asn1/src/asn1_records.hrl
index 43fa61bc5b..55675bee87 100644
--- a/lib/asn1/src/asn1_records.hrl
+++ b/lib/asn1/src/asn1_records.hrl
@@ -99,8 +99,9 @@
 
 %% Code generation parameters and options.
 -record(gen,
-        {erule=ber :: 'ber' | 'per',
+        {erule=ber :: 'ber' | 'per' | 'jer',
          der=false :: boolean(),
+         jer=false :: boolean(),
          aligned=false :: boolean(),
          rec_prefix="" :: string(),
          macro_prefix="" :: string(),
diff --git a/lib/asn1/src/asn1ct.erl b/lib/asn1/src/asn1ct.erl
index cd50d30aa8..5f59abc093 100644
--- a/lib/asn1/src/asn1ct.erl
+++ b/lib/asn1/src/asn1ct.erl
@@ -860,6 +860,7 @@ init_gen_record(EncodingRule, Options) ->
                 _ -> EncodingRule
             end,
     Der = proplists:get_bool(der, Options),
+    Jer = proplists:get_bool(jer, Options) andalso (EncodingRule =/= jer),
     Aligned = EncodingRule =:= per,
     RecPrefix = proplists:get_value(record_name_prefix, Options, ""),
     MacroPrefix = proplists:get_value(macro_name_prefix, Options, ""),
@@ -867,7 +868,7 @@ init_gen_record(EncodingRule, Options) ->
                true -> map;
                false -> record
            end,
-    #gen{erule=Erule,der=Der,aligned=Aligned,
+    #gen{erule=Erule,der=Der,jer=Jer,aligned=Aligned,
          rec_prefix=RecPrefix,macro_prefix=MacroPrefix,
          pack=Pack,options=Options}.
 
@@ -1078,7 +1079,7 @@ get_file_list1(Stream,Dir,Includes,Acc) ->
     end.
 
 get_rule(Options) ->
-    case [Rule || Rule <- [ber,per,uper],
+    case [Rule || Rule <- [ber,per,uper,jer],
 		  Opt <- Options,
 		  Rule =:= Opt] of
 	[Rule] ->
diff --git a/lib/asn1/src/asn1ct_gen.erl b/lib/asn1/src/asn1ct_gen.erl
index 28836ff264..4f8b428b54 100644
--- a/lib/asn1/src/asn1ct_gen.erl
+++ b/lib/asn1/src/asn1ct_gen.erl
@@ -103,7 +103,17 @@ pgen_typeorval(Erules, N2nConvEnums, Code) ->
     pgen_values(Values, Module),
     pgen_objects(Rtmod,Erules,Module,Objects),
     pgen_objectsets(Rtmod,Erules,Module,ObjectSets),
-    pgen_partial_decode(Rtmod,Erules,Module).
+    pgen_partial_decode(Rtmod,Erules,Module),
+        %% If the encoding rule is ber, per or uper and jer is also given as option
+    %% then we generate "extra" support for jer in the same file
+    case Erules#gen.jer of 
+        true ->
+            NewErules = Erules#gen{erule=jer,jer=false},
+            JER_Rtmod = ct_gen_module(NewErules),
+            pgen_types(JER_Rtmod,Erules#gen{erule=jer,jer=false},[],Module,Types);
+        false ->
+            ok
+    end.
 
 %% Generate a function 'V'/0 for each Value V defined in the ASN.1 module.
 %% The function returns the value in an Erlang representation which can be
@@ -655,10 +665,26 @@ pgen_exports(#gen{options=Options}=Gen, Code) ->
             gen_exports(Objects, "enc_", 3),
             gen_exports(Objects, "dec_", 3),
             gen_exports(ObjectSets, "getenc_", 1),
-            gen_exports(ObjectSets, "getdec_", 1);
+            gen_exports(ObjectSets, "getdec_", 1),
+            case Gen#gen.jer of
+                true ->
+                    gen_exports(Types, "typeinfo_", 0);
+                _ ->
+                    true
+            end;
         #gen{erule=per} ->
             gen_exports(Types, "enc_", 1),
-            gen_exports(Types, "dec_", 1)
+            gen_exports(Types, "dec_", 1),
+            case Gen#gen.jer of
+                true ->
+                    gen_exports(Types, "typeinfo_", 0);
+                _ ->
+                    true
+            end;
+        #gen{erule=jer} ->
+            gen_exports(Types, "typeinfo_", 0),
+            gen_exports(ObjectSets, "typeinfo_", 0)
+%%            gen_exports(Types, "dec_", 1)
     end,
 
     A2nNames = [X || {n2n,X} <- Options],
@@ -708,12 +734,20 @@ pgen_dispatcher(Erules, []) ->
     gen_info_functions(Erules);
 pgen_dispatcher(Gen, Types) ->
     %% MODULE HEAD
-    emit(["-export([encode/2,decode/2]).",nl,nl]),
+    emit(["-export([encode/2,decode/2]).",nl]),
+    case Gen#gen.jer of
+        true ->
+            emit(["-export([jer_encode/2,jer_decode/2]).",nl]);
+        false ->
+            ok
+    end,
+    emit([nl]),
     gen_info_functions(Gen),
 
     Options = Gen#gen.options,
     NoFinalPadding = lists:member(no_final_padding, Options),
     NoOkWrapper = proplists:get_bool(no_ok_wrapper, Options),
+    CurrMod = lists:concat(["'",get(currmod),"'"]),
 
     %% ENCODER
     Call = case Gen of
@@ -722,6 +756,11 @@ pgen_dispatcher(Gen, Types) ->
 		   "complete(encode_disp(Type, Data))";
 	       #gen{erule=ber} ->
 		   "iolist_to_binary(element(1, encode_disp(Type, Data)))";
+               #gen{erule=jer} ->
+                   ["?JSON_ENCODE(",
+                    {call,jer,encode_jer,[CurrMod,
+                                          "list_to_existing_atom(lists:concat([typeinfo_,Type]))",
+                                          "Data"]},")"];
 	       #gen{erule=per,aligned=false} when NoFinalPadding ->
 		   asn1ct_func:need({uper,complete_NFP,1}),
 		   "complete_NFP(encode_disp(Type, Data))";
@@ -742,6 +781,27 @@ pgen_dispatcher(Gen, Types) ->
     end,
     emit([nl,nl]),
 
+    case Gen#gen.jer of
+        true ->
+            emit(["jer_encode(Type, Data) ->",nl]),
+            JerCall = ["?JSON_ENCODE(",
+                    {call,jer,encode_jer,
+                     [CurrMod,
+                      "list_to_existing_atom(lists:concat([typeinfo_,Type]))",
+                      "Data"]},")"],
+            case NoOkWrapper of
+                true ->
+                    emit(["  ",JerCall,"."]);
+                false ->
+                    emit(["try ",JerCall," of",nl,
+                          "  Bytes ->",nl,
+                          "    {ok,Bytes}",nl,
+                          try_catch()])
+            end,
+            emit([nl,nl]);
+        false ->
+            ok
+    end,
     %% DECODER
     ReturnRest = proplists:get_bool(undec_rest, Gen#gen.options),
     Data = case Gen#gen.erule =:= ber andalso ReturnRest of
@@ -765,6 +825,10 @@ pgen_dispatcher(Gen, Types) ->
 		asn1ct_func:need({ber,ber_decode_nif,1}),
 		emit(["   {Data,Rest} = ber_decode_nif(Data0),",nl]),
 		"Data";
+	    {#gen{erule=jer},false} ->
+		"?JSON_DECODE(Data)";
+	    {#gen{erule=jer},true} ->
+		exit("JER + return rest not supported");
 	    {_,_} ->
 		"Data"
 	end,
@@ -777,6 +841,11 @@ pgen_dispatcher(Gen, Types) ->
 	{#gen{erule=ber},false} ->
 	    emit(["   Result = ",DecodeDisp,",",nl]),
             result_line(NoOkWrapper, ["Result"]);
+	{#gen{erule=jer},false} ->
+	    emit(["   Result = ",{call,jer,decode_jer,[ CurrMod,
+                                                        "list_to_existing_atom(lists:concat([typeinfo_,Type]))", 
+                                                        DecWrap]},",",nl]),
+            result_line(NoOkWrapper, ["Result"]);
 
 
 	{#gen{erule=per},true} ->
@@ -794,12 +863,43 @@ pgen_dispatcher(Gen, Types) ->
 	    emit([".",nl,nl])
     end,
 
+    case Gen#gen.jer of
+        true ->
+            emit(["jer_decode(Type, ",Data,") ->",nl]),
+            case NoOkWrapper of
+                false -> emit(["try",nl]);
+                true -> ok
+            end,
+            JerDecWrap = "?JSON_DECODE(Data)",
+	    emit(["   Result = ",
+                  {call,jer,
+                   decode_jer,
+                   [CurrMod,
+                    "list_to_existing_atom(lists:concat([typeinfo_,Type]))", 
+                    JerDecWrap]},",",nl]),
+            result_line(false, ["Result"]),
+            case NoOkWrapper of
+                false ->
+                    emit([nl,try_catch(),nl,nl]);
+                true ->
+                    emit([".",nl,nl])
+            end;        
+        false ->
+            ok
+    end,
+    
+
     %% REST of MODULE
     gen_decode_partial_incomplete(Gen),
     gen_partial_inc_dispatcher(Gen),
 
-    gen_dispatcher(Types, "encode_disp", "enc_"),
-    gen_dispatcher(Types, "decode_disp", "dec_").
+    case Gen of
+        #gen{erule=jer} ->
+            ok;
+        _ ->
+            gen_dispatcher(Types, "encode_disp", "enc_"),
+            gen_dispatcher(Types, "decode_disp", "dec_")
+    end.
 
 result_line(NoOkWrapper, Items) ->
     S = ["   "|case NoOkWrapper of
@@ -828,7 +928,8 @@ gen_info_functions(Gen) ->
     Erule = case Gen of
                 #gen{erule=ber} -> ber;
                 #gen{erule=per,aligned=false} -> uper;
-                #gen{erule=per,aligned=true} -> per
+                #gen{erule=per,aligned=true} -> per;
+                #gen{erule=jer} -> jer
             end,
     Maps = case Gen of
                #gen{pack=record} -> false;
@@ -980,6 +1081,8 @@ do_emit({var,Variable}) when is_atom(Variable) ->
     [Head-32|V];
 do_emit({asis,What}) ->
     io_lib:format("~w", [What]);
+do_emit({asisp,What}) ->
+    io_lib:format("~p", [What]);
 do_emit({call,M,F,A}) ->
     MFA = {M,F,length(A)},
     asn1ct_func:need(MFA),
@@ -1201,7 +1304,9 @@ gen_head(#gen{options=Options}=Gen, Mod, Hrl) ->
                #gen{erule=per,aligned=true} ->
                    "PER (aligned)";
                #gen{erule=ber} ->
-                   "BER"
+                   "BER";
+               #gen{erule=jer} ->
+                   "JER (JSON)"
            end,
     emit(["%% Generated by the Erlang ASN.1 ",Name,
           " compiler. Version: ",asn1ct:vsn(),nl,
@@ -1216,8 +1321,27 @@ gen_head(#gen{options=Options}=Gen, Mod, Hrl) ->
     end,
     emit(["-asn1_info([{vsn,'",asn1ct:vsn(),"'},",nl,
 	  "            {module,'",Mod,"'},",nl,
-	  "            {options,",io_lib:format("~p",[Options]),"}]).",nl,nl]).
-
+	  "            {options,",io_lib:format("~p",[Options]),"}]).",nl,nl]),
+    JerDefines = case Gen of
+                     #gen{erule=jer} ->
+                         true;
+                     #gen{jer=true} ->
+                         true;
+                     _ ->
+                         false
+                 end,
+    JerDefines andalso 
+%% FIXME add jiffy as well and maybe a third argument where the user
+%% can provide the JSON encode/decode as a fun (or atom).
+        emit([
+              "-ifdef(jsone).",nl,
+              "-define(JSON_DECODE(Data),jsone:decode(Data)).",nl,
+              "-define(JSON_ENCODE(Term),jsone:encode(Term)).",nl,
+              "-else.",nl,
+              "-define(JSON_DECODE(Data),jsx:decode(Data,[return_maps])).",nl,
+              "-define(JSON_ENCODE(Term),jsx:encode(Term)).",nl,
+              "-endif.",nl
+             ]).
 
 gen_hrlhead(Mod) ->
     emit(["%% Generated by the Erlang ASN.1 compiler. Version: ",
@@ -1430,6 +1554,7 @@ get_fieldtype([Field|Rest],FieldName) ->
 %% 
 %% used to output function names in generated code.
 
+
 list2name(L) ->
     NewL = list2name1(L),
     lists:concat(lists:reverse(NewL)).
@@ -1442,8 +1567,8 @@ list2name1([{ptype,H}|_T]) ->
     [H];
 list2name1([H|_T]) ->
     [H];
-list2name1([]) ->
-    [].
+list2name1(H) ->
+    H.
 
 
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -1485,10 +1610,15 @@ index2suffix(N) ->
 ct_gen_module(#gen{erule=ber}) ->
     asn1ct_gen_ber_bin_v2;
 ct_gen_module(#gen{erule=per}) ->
-    asn1ct_gen_per.
+    asn1ct_gen_per;
+ct_gen_module(#gen{erule=jer}) ->
+    asn1ct_gen_jer.
+
 
 ct_constructed_module(#gen{erule=ber}) ->
     asn1ct_constructed_ber_bin_v2;
+ct_constructed_module(#gen{erule=jer}) ->
+    asn1ct_gen_jer;
 ct_constructed_module(#gen{erule=per}) ->
     asn1ct_constructed_per.
 
diff --git a/lib/asn1/src/asn1ct_gen_jer.erl b/lib/asn1/src/asn1ct_gen_jer.erl
new file mode 100644
index 0000000000..041ea6b247
--- /dev/null
+++ b/lib/asn1/src/asn1ct_gen_jer.erl
@@ -0,0 +1,605 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2019-2020. All Rights Reserved.
+%%
+%% Licensed under the Apache License, Version 2.0 (the "License");
+%% you may not use this file except in compliance with the License.
+%% You may obtain a copy of the License at
+%%
+%%     http://www.apache.org/licenses/LICENSE-2.0
+%%
+%% Unless required by applicable law or agreed to in writing, software
+%% distributed under the License is distributed on an "AS IS" BASIS,
+%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+%% See the License for the specific language governing permissions and
+%% limitations under the License.
+%%
+%% %CopyrightEnd%
+%%
+%%
+-module(asn1ct_gen_jer).
+
+%% Generate erlang module which handles (PER) encode and decode for
+%% all types in an ASN.1 module
+
+-include("asn1_records.hrl").
+
+-export([gen_encode/2,gen_encode/3,gen_decode/2,gen_decode/3]).
+-export([gen_encode_prim/3]).
+-export([gen_dec_prim/2]).
+-export([gen_objectset_code/2, gen_obj_code/3]).
+-export([gen_inc_decode/2,gen_decode_selected/3]).
+-export([extaddgroup2sequence/1]).
+-export([dialyzer_suppressions/1]).
+
+-export([gen_encode_constructed/4]).
+-export([gen_encode_sequence/3]).
+-export([gen_decode_sequence/3]).
+-export([gen_encode_set/3]).
+-export([gen_decode_set/3]).
+-export([gen_encode_sof/4]).
+-export([gen_decode_sof/4]).
+-export([gen_encode_choice/3]).
+-export([gen_decode_choice/3]).
+
+
+-import(asn1ct_gen, [emit/1]).
+
+
+
+%%==========================================================================
+%%  Encode/decode SEQUENCE (and SET)
+%%==========================================================================
+
+gen_encode_sequence(Gen, Typename, #type{}=D) ->
+    
+    {_SeqOrSet,TableConsInfo,CompList0} =
+	case D#type.def of
+	    #'SEQUENCE'{tablecinf=TCI,components=CL} -> 
+		{'SEQUENCE',TCI,CL};
+	    #'SET'{tablecinf=TCI,components=CL} -> 
+		{'SET',TCI,CL}
+	end,
+    %% filter away extensionAdditiongroup markers
+    CompList = filter_complist(CompList0),
+    CompList1 = case CompList of
+		    {Rl1,El,Rl2} -> Rl1 ++ El ++ Rl2;
+		    {Rl,El} -> Rl ++ El;
+		    _ -> CompList
+		end,
+
+    %%    enc_match_input(Gen, ValName, CompList1),
+
+    EncObj =
+	case TableConsInfo of
+	    #simpletableattributes{usedclassfield=Used,
+				   uniqueclassfield=Unique} when Used /= Unique ->
+		false;
+	    %% ObjectSet, name of the object set in constraints
+	    #simpletableattributes{objectsetname=ObjectSetRef,
+				   c_name=AttrN,
+				   c_index=N,
+				   usedclassfield=UniqueFieldName,
+				   uniqueclassfield=UniqueFieldName,
+				   valueindex=_ValueIndex} -> %% N is index of attribute that determines constraint
+		{ObjSetMod,ObjSetName} = ObjectSetRef,
+		OSDef = asn1_db:dbget(ObjSetMod, ObjSetName),
+		case (OSDef#typedef.typespec)#'ObjectSet'.gen of
+		    true ->
+			{AttrN,N};
+		    _ ->
+			false
+		end;
+	    _ ->
+		case D#type.tablecinf of
+		    [{objfun,_}|_] ->
+			%% when the simpletableattributes was at an outer
+			%% level and the objfun has been passed through the
+			%% function call
+			{"got objfun through args","ObjFun"};
+		    _ ->
+			false
+		end
+	end,
+    CompTypes = gen_enc_comptypes(Gen, Typename, CompList1, 1, EncObj, []),
+    Prefix = asn1ct_gen:get_record_name_prefix(Gen),
+    {sequence,
+     list_to_atom(lists:concat([Prefix,asn1ct_gen:list2name(Typename)])),
+     length(CompList1),CompTypes}.
+
+gen_decode_sequence(_,_,_) -> ok.
+
+
+%%============================================================================
+%%  Encode/decode SET
+%%============================================================================
+
+gen_encode_set(Erules,Typename,D) when is_record(D,type) ->
+    gen_encode_sequence(Erules,Typename,D).
+
+gen_decode_set(_,_,_) -> ok.
+
+
+%%===============================================================================
+%%  Encode/decode SEQUENCE OF and SET OF
+%%===============================================================================
+
+gen_encode_sof(Erules,Typename,InnerTypename,D) when is_record(D,type) ->
+    asn1ct_name:start(),
+    {_SeqOrSetOf, Cont} = D#type.def,
+
+%%    Objfun = case D#type.tablecinf of
+%%		 [{objfun,_}|_R] ->
+%%		     ", ObjFun";
+%%		 _ ->
+%%		     ""
+%%	     end,
+
+%%    emit(["   EncV = 'enc_",asn1ct_gen:list2name(Typename),
+%%	  "_components'(Val",Objfun,",[]).",nl,nl]),
+    NameSuffix = asn1ct_gen:constructed_suffix(InnerTypename,D#type.def),
+    {sof,gen_typeinfo(Erules,[NameSuffix|Typename],Cont)}.
+    
+gen_decode_sof(_,_,_,_) -> ok.
+
+%%============================================================================
+%%  Encode/decode CHOICE
+%%
+%%============================================================================
+
+gen_encode_choice(Erules,TypeName,D) when is_record(D,type) ->
+    {'CHOICE',CompList} = D#type.def,
+    CompList1 = case CompList of
+		    {Rl1,El,Rl2} -> Rl1 ++ El ++ Rl2;
+		    {Rl,El} -> Rl ++ El;
+		    _ -> CompList
+		end,
+    {choice,maps:from_list(
+              [{AltName,AltType}||
+                  {AltName,AltType,_OptOrMand} <- 
+                      gen_enc_comptypes(Erules,TypeName,CompList1,0,0,[])])}.
+
+gen_decode_choice(_,_,_) -> ok.
+
+
+%%============================================================================
+%%  Encode SEQUENCE
+%%
+%%============================================================================
+
+gen_enc_comptypes(Erules,TopType,[#'ComponentType'{name=Cname,typespec=Type,prop=Prop}|Rest],Pos,EncObj,Acc) ->
+    TypeInfo = 
+        gen_enc_line(Erules,TopType,Cname,Type,"Dummy",
+                                    3,Prop,EncObj),
+    gen_enc_comptypes(Erules,TopType,Rest,Pos,EncObj,[{atom_to_binary(Cname,utf8),TypeInfo,Prop}|Acc]);
+gen_enc_comptypes(_,_,[],_,_,Acc) ->
+    lists:reverse(Acc).
+
+gen_enc_classtypes(Erules,TopType,[{TName,#typedef{typespec=TSpec}}|Rest],Acc) ->
+    TypeInfo = 
+        gen_enc_line(Erules,TopType,TName,TSpec,"Dummy",
+                                    3,mandatory,false),
+    gen_enc_classtypes(Erules,TopType,Rest,[{TName,TypeInfo}|Acc]);
+gen_enc_classtypes(_,_,[],Acc) ->
+    lists:reverse(Acc).
+
+%%============================================================================
+%%  Decode SEQUENCE
+%%
+%%============================================================================
+
+gen_enc_line(Erules,TopType,Cname,
+	     Type=#type{constraint=C,
+			def=#'ObjectClassFieldType'{type={typefield,_}}},
+	     Element,Indent,OptOrMand=mandatory,EncObj) 
+  when is_list(Element) ->
+    case asn1ct_gen:get_constraint(C,componentrelation) of
+	{componentrelation,_,_} ->
+	    gen_enc_line(Erules,TopType,Cname,Type,Element,Indent,OptOrMand,
+			 ["{",{curr,tmpBytes},",_} = "],EncObj);
+	_ ->
+	    gen_enc_line(Erules,TopType,Cname,Type,Element,Indent,OptOrMand,
+			 ["{",{curr,encBytes},",",{curr,encLen},"} = "],
+			 EncObj)
+    end;
+gen_enc_line(Erules,TopType,Cname,Type,Element,Indent,OptOrMand,EncObj) 
+  when is_list(Element) ->
+    gen_enc_line(Erules,TopType,Cname,Type,Element,Indent,OptOrMand,
+		 [{curr,encV}," = "],EncObj).
+
+gen_enc_line(Erules,TopType,Cname,Type,Element,_Indent,_OptOrMand,_Assign,EncObj)
+  when is_list(Element) ->
+    InnerType = case Type of
+                    #type{def=Def} -> 
+                        asn1ct_gen:get_inner(Def);
+                    #'ObjectSet'{class=ExtRef} ->
+                        asn1ct_gen:get_inner(ExtRef)
+                end,
+    WhatKind = asn1ct_gen:type(InnerType),
+%%    emit(IndDeep),
+%%    emit(Assign),
+%%    gen_optormand_case(OptOrMand, Erules, TopType, Cname, Type, Element),
+        CR = case Type of 
+                 #type{constraint = Constraint} ->
+                     asn1ct_gen:get_constraint(Constraint,componentrelation);
+                 _ ->
+                     []
+             end,
+    TypeInfo =
+        case {Type,CR} of
+            {#type{def=#'ObjectClassFieldType'{type={typefield,_},
+                                               fieldname=RefedFieldName}},
+             {componentrelation,_,_}} ->
+                {Name,_RestFieldNames} = RefedFieldName,
+                true = is_atom(Name),                %Assertion.
+                {'ObjClassFieldType',EncObj,CR};
+            _ ->
+                case WhatKind of
+                    {primitive,bif} ->
+                        gen_encode_prim(jer, Type, Element);
+                    'ASN1_OPEN_TYPE' ->
+                        case Type#type.def of
+                            #'ObjectClassFieldType'{} -> %Open Type
+                                gen_encode_prim(jer,#type{def='ASN1_OPEN_TYPE'},Element);
+                            _ ->
+                                gen_encode_prim(jer,Type, Element)
+                        end;
+                    {constructed,bif} ->
+                        Typename = [Cname|TopType],
+                        gen_encode_constructed(Erules,Typename,InnerType,Type);
+                    #'Externaltypereference'{module=Mod,type=EType} ->
+                        {typeinfo,{Mod,typeinfo_func(EType)}}
+
+%%                     _ ->
+
+%% %%                            mkfuncname(TopType,Cname,InnerType,WhatKind,"typeinfo_",""),
+%%                         case {WhatKind,Type#type.tablecinf,EncObj} of
+%%                             {{constructed,bif},[{objfun,_}|_R],{_,Fun}} ->
+%%                                 emit([EncFunName,"(",Element,
+%%                                       ", ",Fun,")"]);
+%%                             _ ->
+%%                                 {typeinfo,EncFunName}
+%%
+%%                        end
+                end
+        end,
+    TypeInfo.
+
+%%------------------------------------------------------
+%% General and special help functions (not exported)
+%%------------------------------------------------------
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% filter away ExtensionAdditionGroup start and end marks since these
+%% have no significance for the JER encoding
+%%
+filter_complist(CompList) when is_list(CompList) ->
+    lists:filter(fun(#'ExtensionAdditionGroup'{}) ->
+			 false;
+		    ('ExtensionAdditionGroupEnd') ->
+			 false;
+		    (_) ->
+			 true
+		 end, CompList);
+filter_complist({Root,Ext}) ->
+    {Root,filter_complist(Ext)};
+filter_complist({Root1,Ext,Root2}) ->
+    {Root1,filter_complist(Ext),Root2}.
+
+%%name2bin(TypeName) ->
+%%    NameAsList = asn1ct_gen:list2name(TypeName),
+%%    list_to_binary(NameAsList).
+
+gen_encode_constructed(Erules,Typename,InnerType,D) when is_record(D,type) ->
+    case InnerType of
+	'SET' ->
+	    gen_encode_set(Erules,Typename,D);
+	'SEQUENCE' ->
+	    gen_encode_sequence(Erules,Typename,D);
+	'CHOICE' ->
+	    gen_encode_choice(Erules,Typename,D);
+	'SEQUENCE OF' ->
+	    gen_encode_sof(Erules,Typename,InnerType,D);
+	'SET OF' ->
+	    gen_encode_sof(Erules,Typename,InnerType,D)
+    end.
+
+
+%% empty_lb(#gen{erule=jer}) ->
+%%     null.
+
+%% value_match(#gen{pack=record}, VIs, Value) ->
+%%     value_match_rec(VIs, Value);
+%% value_match(#gen{pack=map}, VIs, Value) ->
+%%     value_match_map(VIs, Value).
+
+%% value_match_rec([], Value) ->
+%%     Value;
+%% value_match_rec([{VI,_}|VIs], Value0) ->
+%%     Value = value_match_rec(VIs, Value0),
+%%     lists:concat(["element(",VI,", ",Value,")"]).
+
+%% value_match_map([], Value) ->
+%%     Value;
+%% value_match_map([{_,Name}|VIs], Value0) ->
+%%     Value = value_match_map(VIs, Value0),
+%%     lists:concat(["maps:get(",Name,", ",Value,")"]).
+
+%% call(F, Args) ->
+%%     asn1ct_func:call(jer, F, Args).
+
+%%===============================================================================
+%%===============================================================================
+%%===============================================================================
+%% Generate ENCODING
+%%===============================================================================
+%%===============================================================================
+%%===============================================================================
+
+dialyzer_suppressions(_) ->
+    case asn1ct:use_legacy_types() of
+	false -> ok;
+	true -> suppress({ber,encode_bit_string,4})
+    end,
+    suppress({ber,decode_selective,2}),
+    emit(["    ok.",nl]).
+
+suppress({M,F,A}=MFA) ->
+    case asn1ct_func:is_used(MFA) of
+	false ->
+	    ok;
+	true ->
+	    Args = [lists:concat(["element(",I,", Arg)"]) || I <- lists:seq(1, A)],
+	    emit(["    ",{call,M,F,Args},com,nl])
+    end.
+
+%%===============================================================================
+%% encode #{typedef, {pos, name, typespec}}
+%%===============================================================================
+
+gen_encode(Erules, #typedef{}=D) ->
+    gen_encode_user(Erules, D, true).
+
+%%===============================================================================
+%% encode #{type, {tag, def, constraint}}
+%%===============================================================================
+
+gen_encode(Erules,Typename,Type) when is_record(Type,type) ->
+    InnerType = asn1ct_gen:get_inner(Type#type.def),
+    ObjFun =
+	case lists:keysearch(objfun,1,Type#type.tablecinf) of
+	    {value,{_,_Name}} ->
+		", ObjFun";
+	    false ->
+		""
+	end,
+
+    case asn1ct_gen:type(InnerType) of
+	{constructed,bif} ->
+            Func = {asis,enc_func(asn1ct_gen:list2name(Typename))},
+	    emit([nl,nl,nl,"%%================================",nl,
+                  "%%  ",asn1ct_gen:list2name(Typename),nl,
+                  "%%================================",nl,
+                  Func,"(Val",ObjFun,") ->",nl,
+                  "   "]),
+	    TypeInfo = gen_encode_constructed(Erules,Typename,InnerType,Type),
+            emit([{asis,TypeInfo},".",nl]);
+	_ ->
+	    true
+    end;
+
+%%===============================================================================
+%% encode ComponentType
+%%===============================================================================
+
+gen_encode(Erules,Tname,#'ComponentType'{name=Cname,typespec=Type}) ->
+    NewTname = [Cname|Tname],
+    %% The tag is set to [] to avoid that it is
+    %% taken into account twice, both as a component/alternative (passed as
+    %% argument to the encode decode function and within the encode decode
+    %% function it self.
+    NewType = Type#type{tag=[]},
+    gen_encode(Erules,NewTname,NewType).
+
+gen_encode_user(Erules, #typedef{}=D, _Wrapper) ->
+    Typename = [D#typedef.name],
+    Type = D#typedef.typespec,
+    InnerType = asn1ct_gen:get_inner(Type#type.def),
+    emit([nl,nl,"%%================================"]),
+    emit([nl,"%%  ",Typename]),
+    emit([nl,"%%================================",nl]),
+    FuncName = {asis,typeinfo_func(asn1ct_gen:list2name(Typename))},
+    emit([FuncName,"() ->",nl]),
+    CurrentMod = get(currmod),
+    TypeInfo = 
+        case asn1ct_gen:type(InnerType) of
+            {constructed,bif} ->
+                gen_encode_constructed(Erules,Typename,InnerType,Type);
+            {primitive,bif} ->
+                gen_encode_prim(jer,Type,"Val");
+            #'Externaltypereference'{module=CurrentMod,type=Etype} ->
+                {typeinfo,{CurrentMod,typeinfo_func(Etype)}};
+            #'Externaltypereference'{module=Emod,type=Etype} ->
+                {typeinfo,{Emod,typeinfo_func(Etype)}};
+            'ASN1_OPEN_TYPE' ->	    
+                gen_encode_prim(jer,
+                                Type#type{def='ASN1_OPEN_TYPE'},
+                                "Val")
+        end,
+    emit([{asis,TypeInfo},".",nl,nl]).
+
+gen_typeinfo(Erules, Typename, Type) ->
+    InnerType = asn1ct_gen:get_inner(Type#type.def),
+    CurrentMod = get(currmod),
+    case asn1ct_gen:type(InnerType) of
+	{constructed,bif} ->
+	    gen_encode_constructed(Erules,Typename,InnerType,Type);
+	{primitive,bif} ->
+	    gen_encode_prim(jer,Type,"Val");
+	#'Externaltypereference'{module=CurrentMod,type=Etype} ->
+	    {typeinfo,{CurrentMod,typeinfo_func(Etype)}};
+	#'Externaltypereference'{module=Emod,type=Etype} ->
+	    {typeinfo,{Emod,typeinfo_func(Etype)}};
+	'ASN1_OPEN_TYPE' ->
+	    gen_encode_prim(jer,
+			    Type#type{def='ASN1_OPEN_TYPE'},
+			    "Val")
+    end.
+
+gen_encode_prim(_Erules, #type{}=D, _Value) ->
+    BitStringConstraint = get_size_constraint(D#type.constraint),    
+    IntConstr = int_constr(D#type.constraint),
+
+    %% MaxBitStrSize = case BitStringConstraint of
+    %%     		[] -> none;
+    %%     		{_,'MAX'} -> none;
+    %%     		{_,Max} -> Max;
+    %%     		Max when is_integer(Max) -> Max
+    %%     	    end,
+    asn1ct_name:new(enumval),
+    Type = case D#type.def of
+	       'OCTET STRING'    -> maybe_legacy_octet_string();
+               'UTF8String'      -> string;
+	       'ObjectDescriptor'-> string;
+	       'NumericString'   -> string;
+	       'TeletexString'   -> string;
+	       'T61String'       -> string;
+	       'VideotexString'  -> string;
+	       'GraphicString'   -> string;
+	       'VisibleString'   -> string;
+	       'GeneralString'   -> string;
+	       'PrintableString' -> string;
+	       'IA5String'       -> string;
+	       'UTCTime'         -> string;
+	       'GeneralizedTime' -> string;
+               B1 = 'BIT STRING' -> maybe_legacy_bit_string(B1,BitStringConstraint);
+               B2 = {'BIT STRING',_NNL} -> 
+                   maybe_legacy_bit_string(B2,BitStringConstraint);
+               {'INTEGER',NNL} -> {'INTEGER_NNL',NNL};
+               {'ENUMERATED',{NNL,Ext}} -> {'ENUMERATED_EXT',maps:from_list(NNL++Ext)};
+               {'ENUMERATED',NNL} -> {'ENUMERATED',maps:from_list(NNL)};
+	       Other             -> Other
+	   end,
+    case IntConstr of
+        [] -> % No constraint
+            Type;
+        _ ->
+            {Type,IntConstr}
+    end.
+
+maybe_legacy_octet_string() ->
+    case asn1ct:use_legacy_types() of
+        true ->
+            legacy_octet_string;
+        false ->
+            octet_string
+    end.
+
+maybe_legacy_bit_string(BitStrType,SizeConstraint) ->
+    Type = case asn1ct:get_bit_string_format() of
+               bitstring ->
+                   bit_string;
+               compact ->
+                   compact_bit_string;
+               legacy ->
+                   legacy_bit_string
+           end,
+    Type1 = case BitStrType of
+                {'BIT STRING',[]} -> 
+                    Type;
+                'BIT STRING' -> 
+                    Type;
+                {'BIT STRING',NNL} -> 
+                    {list_to_atom(lists:concat([Type,"_nnl"])),NNL}
+            end,
+    case SizeConstraint of
+        S when is_integer(S) ->
+            {Type1,S};
+        _ ->
+            Type1
+    end.
+%%===========================================================================
+%% Generate DECODING
+%%===========================================================================
+%% dummy functions beause we don't generate anything special for decode 
+%%===========================================================================
+
+gen_decode(_,_) -> ok.
+
+gen_inc_decode(_Erules,_Type) -> ok.
+
+%% gen_decode_selected exported function for selected decode
+%% Is not supported and should not be called for JER
+gen_decode_selected(_Erules,_Type,_FuncName) -> ok. 
+
+gen_decode(_,_,_) -> ok.
+
+gen_dec_prim(_Att, _BytesVar) -> ok.
+
+%% Simplify an integer constraint so that we can efficiently test it.
+-spec int_constr(term()) -> [] | {integer(),integer()|'MAX'}.
+int_constr(C) ->
+    case asn1ct_imm:effective_constraint(integer, C) of
+	[{_,[]}] ->
+	    %% Extension - ignore constraint.
+	    [];
+	[{'ValueRange',{'MIN',_}}] ->
+	    %% Tricky to implement efficiently - ignore it.
+	    [];
+	[{'ValueRange',{_,_}=Range}] ->
+	    Range;
+	[{'SingleValue',Sv}] ->
+	    Sv;
+	[] ->
+	    []
+    end.
+
+gen_obj_code(_Erules,_Module,_Obj) -> ok.
+
+gen_objectset_code(Erules,ObjSet) ->
+    ObjSetName = ObjSet#typedef.name,
+    Def = ObjSet#typedef.typespec,
+    Set = Def#'ObjectSet'.set,
+    emit([nl,nl,nl,
+          "%%================================",nl,
+          "%%  ",ObjSetName,nl,
+          "%%================================",nl]),
+    FuncName = {asis,typeinfo_func(asn1ct_gen:list2name([ObjSetName]))},
+    SelectValMap = 
+        maps:from_list([{SelectVal,
+                         maps:from_list(
+                           gen_enc_classtypes(Erules,ObjSetName,
+                                             [TNameType || TNameType = {_TypeName,#typedef{}} <-TypeList],
+                                             []))} || {_,SelectVal,TypeList} <- Set]),
+    emit([FuncName,"() ->",nl]),
+    emit([{asis,SelectValMap},".",nl]).
+
+
+get_size_constraint(C) ->
+    case lists:keyfind('SizeConstraint', 1, C) of
+	false -> [];
+	{_,{_,[]}} -> [];			%Extensible.
+	{_,{Sv,Sv}} -> Sv;
+	{_,{_,_}=Tc} -> Tc
+    end.
+ 
+
+%% For BER the ExtensionAdditionGroup notation has no impact on the
+%% encoding/decoding. Therefore we can filter away the
+%% ExtensionAdditionGroup start and end markers.
+extaddgroup2sequence(ExtList) when is_list(ExtList) ->
+    lists:filter(fun(#'ExtensionAdditionGroup'{}) ->
+			 false;
+		    ('ExtensionAdditionGroupEnd') ->
+			 false;
+		    (_) ->
+			 true
+		 end, ExtList).
+
+typeinfo_func(Tname) ->
+    list_to_atom(lists:concat(["typeinfo_",Tname])).    
+
+enc_func(Tname) ->
+    list_to_atom(lists:concat(["enc_",Tname])).
diff --git a/lib/asn1/src/asn1ct_value.erl b/lib/asn1/src/asn1ct_value.erl
index 05fe2f4ef4..af97e042b4 100644
--- a/lib/asn1/src/asn1ct_value.erl
+++ b/lib/asn1/src/asn1ct_value.erl
@@ -127,16 +127,29 @@ get_sequence(M,Typename,Type) ->
     end.
 
 get_components(M,Typename,{Root,Ext}) ->
-    get_components(M,Typename,Root++Ext);
+    get_components2(M,Typename,filter_complist(Root++Ext));
+get_components(M,Typename,{Rl1,El,Rl2}) ->
+    get_components2(M,Typename,filter_complist(Rl1++El++Rl2));
+get_components(M,Typename,CompList) ->
+    get_components2(M,Typename,CompList).
 
 %% Should enhance this *** HERE *** with proper handling of extensions
 
-get_components(M, Typename, [H|T]) ->
+get_components2(M, Typename, [H|T]) ->
     #'ComponentType'{name=Name} = H,
     [{Name,from_type(M, Typename, H)}|get_components(M, Typename, T)];
-get_components(_,_,[]) ->
+get_components2(_,_,[]) ->
     [].
 
+filter_complist(CompList) when is_list(CompList) ->
+    lists:filter(fun(#'ExtensionAdditionGroup'{}) ->
+			 false;
+		    ('ExtensionAdditionGroupEnd') ->
+			 false;
+		    (_) ->
+			 true
+		 end, CompList).
+
 get_choice(M,Typename,Type) ->
     {'CHOICE',TCompList} = Type#type.def,
     case TCompList of
diff --git a/lib/asn1/src/asn1rtt_jer.erl b/lib/asn1/src/asn1rtt_jer.erl
new file mode 100644
index 0000000000..277686df02
--- /dev/null
+++ b/lib/asn1/src/asn1rtt_jer.erl
@@ -0,0 +1,501 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 2012-2017. All Rights Reserved.
+%%
+%% Licensed under the Apache License, Version 2.0 (the "License");
+%% you may not use this file except in compliance with the License.
+%% You may obtain a copy of the License at
+%%
+%%     http://www.apache.org/licenses/LICENSE-2.0
+%%
+%% Unless required by applicable law or agreed to in writing, software
+%% distributed under the License is distributed on an "AS IS" BASIS,
+%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+%% See the License for the specific language governing permissions and
+%% limitations under the License.
+%%
+%% %CopyrightEnd%
+%%
+
+-module(asn1rtt_jer).
+%% encoding / decoding of BER
+-ifdef(DEBUG).
+-compile(export_all).
+-endif.
+%% For typeinfo JER
+-export([encode_jer/3, decode_jer/3]).
+
+
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+%% Common code for all JER encoding/decoding
+%%
+%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
+encode_jer(Module,InfoFunc,Val) ->
+    Info = Module:InfoFunc(),
+    encode_jer(Info,Val).
+
+%% {sequence,
+%%    Name::atom() % The record name used for the sequence 
+%%    Arity::integer() % number of components
+%%    CompInfos::[CompInfo()] % list of components with name, type etc
+%%    Value::record matching name and arity
+
+encode_jer({sequence_tab,Simple,Sname,Arity,CompInfos},Value) 
+  when tuple_size(Value) == Arity+1 ->
+    [Sname|Clist] = tuple_to_list(Value),
+    encode_jer_component_tab(CompInfos,Clist,Simple,#{});
+%% {sequence,
+%%    Name::atom() % The record name used for the sequence 
+%%    Arity::integer() % number of components
+%%    CompInfos::[CompInfo()] % list of components with name, type etc
+%%    Value::record matching name and arity
+encode_jer({sequence,Sname,Arity,CompInfos},Value) 
+  when tuple_size(Value) == Arity+1 ->
+    [Sname|Clist] = tuple_to_list(Value),
+    encode_jer_component(CompInfos,Clist,#{});
+encode_jer(string,Str) when is_list(Str) ->
+    list_to_binary(Str);
+encode_jer({string,_Prop},Str) when is_list(Str) ->
+    list_to_binary(Str);
+encode_jer(string,Str) when is_binary(Str) ->
+    Str;
+encode_jer({string,_Prop},Str) when is_binary(Str) ->
+    Str;
+encode_jer('INTEGER',Int) when is_integer(Int) ->
+    Int;
+encode_jer({'INTEGER',{Min,Max}},Int) when is_integer(Int),Max >=Int, Int >= Min ->
+    Int;
+encode_jer({'INTEGER_NNL',_NNL},Int) when is_integer(Int) ->
+    Int;
+encode_jer(Type = {'INTEGER_NNL',NNList},Int) when is_atom(Int) ->
+    case lists:keyfind(Int, 1, NNList) of
+        {_, NewVal} ->
+            NewVal;
+        _ ->
+            exit({error, {asn1, {Type,Int}}})
+    end;
+encode_jer({Type = {'INTEGER_NNL',_NNList},_Constraint},Int) when is_atom(Int) ->
+    encode_jer(Type,Int);
+encode_jer({{'INTEGER_NNL',_NNList},Constraint},Int) when is_integer(Int) ->
+    encode_jer({'INTEGER',Constraint},Int);
+encode_jer('BOOLEAN',Bool) when is_boolean(Bool) ->
+    Bool;
+encode_jer({'BOOLEAN',_Prop},Bool) when is_boolean(Bool) ->
+    Bool;
+encode_jer('NULL',_) ->
+    null;
+encode_jer(legacy_octet_string, Value) when is_list(Value) ->
+    bitstring2json(list_to_binary(Value));
+encode_jer({legacy_octet_string,_Prop}, Value) when is_list(Value) ->
+    bitstring2json(list_to_binary(Value));
+encode_jer(octet_string,Value) when is_binary(Value) ->
+    encode_jer({octet_string,[]}, Value);
+encode_jer({octet_string,_Prop}, Value) when is_binary(Value) ->
+    bitstring2json(Value);
+
+encode_jer({'ENUMERATED',EnumMap},Val) when is_map_key(Val,EnumMap) ->
+    Val;
+encode_jer({Type = {'ENUMERATED',_EnumList},_Constr}, Val) ->
+    encode_jer(Type,Val);
+
+encode_jer({'ENUMERATED_EXT',_EnumMap},Val) when is_atom(Val) ->
+    Val;
+encode_jer({Type = {'ENUMERATED_EXT',_EnumList},_Constr}, Val) ->
+    encode_jer(Type,Val);
+
+encode_jer({typeinfo,{Module,Func}},Val) ->
+    TypeInfo = Module:Func(),
+    encode_jer(TypeInfo,Val);
+ 
+encode_jer({sof,Type},Vals) when is_list(Vals) ->
+    [encode_jer(Type,Val)||Val <- Vals];
+encode_jer({choice,Choices},{Alt,Value}) ->
+    case is_map_key(AltBin = atom_to_binary(Alt,utf8),Choices) of
+        true ->
+            EncodedVal = encode_jer(maps:get(AltBin,Choices),Value),
+            #{AltBin => EncodedVal};
+        false ->
+            exit({error,{asn1,{invalid_choice,Alt,Choices}}})
+    end;
+    
+encode_jer(bit_string,Value) ->
+    Str = bitstring2json(Value),
+    #{value => Str, length => bit_size(Value)};
+encode_jer({bit_string,FixedLength},Value) when is_bitstring(Value), is_integer(FixedLength) ->
+    Value2 = jer_padbitstr(Value,FixedLength),
+    bitstring2json(Value2);
+encode_jer(compact_bit_string,Compact) ->
+    BitStr = jer_compact2bitstr(Compact),
+    encode_jer(bit_string,BitStr);
+encode_jer({compact_bit_string,FixedLength},Compact = {_Unused,Binary}) when is_binary(Binary) ->
+    BitStr = jer_compact2bitstr(Compact),
+    encode_jer({bit_string,FixedLength},BitStr);
+encode_jer({bit_string_nnl,NNL},Value) -> 
+    Value1 = jer_bit_str2bitstr(Value,NNL),
+    encode_jer(bit_string,Value1);
+encode_jer({{bit_string_nnl,NNL},FixedLength},Value) ->
+    Value1 = jer_bit_str2bitstr(Value,NNL),
+    encode_jer({bit_string,FixedLength},Value1);
+encode_jer({compact_bit_string_nnl,NNL},Value) ->
+    Value1 = jer_bit_str2bitstr(Value,NNL),
+    encode_jer(bit_string,Value1);
+encode_jer({{compact_bit_string_nnl,NNL},FixedLength},Value) ->
+    Value1 = jer_bit_str2bitstr(Value,NNL),
+    encode_jer({bit_string,FixedLength},Value1);
+%%encode_jer({legacy_bit_string_nnl,NNL},Value) ->
+%%encode_jer({{legacy_bit_string_nnl,NNL},FixedLength},Value) ->
+encode_jer('OBJECT IDENTIFIER',Oid) when is_tuple(Oid) ->
+    oid2json(Oid);
+encode_jer('RELATIVE-OID',Oid) when is_tuple(Oid) ->
+    oid2json(Oid);
+encode_jer({'ObjClassFieldType',_,_},Val) when is_binary(Val)->
+    Val;
+encode_jer('ASN1_OPEN_TYPE',Val) when is_binary(Val) ->
+    Val;
+    
+encode_jer(Type,Val) ->
+    exit({error,{asn1,{{encode,Type},Val}}}).
+
+
+encode_jer_component_tab([{_Name, _Type, 'OPTIONAL'} | CompInfos], [asn1_NOVALUE | Rest], Simple, MapAcc) ->
+    encode_jer_component_tab(CompInfos, Rest, Simple, MapAcc);
+encode_jer_component_tab([{_Name, _Type, {'DEFAULT',_}} | CompInfos], [asn1_DEFAULT | Rest], Simple, MapAcc) ->
+    encode_jer_component_tab(CompInfos, Rest, Simple, MapAcc);
+encode_jer_component_tab([{Name, Type, _OptOrDefault} | CompInfos], [Value | Rest], Simple, MapAcc) ->
+    Enc = encode_jer(Type, Value),
+    encode_jer_component_tab(CompInfos, Rest, Simple, MapAcc#{Name => Enc});
+encode_jer_component_tab([], _, _Simple, MapAcc) ->
+    MapAcc.
+
+encode_jer_component([{_Name, _Type, 'OPTIONAL'} | CompInfos], [asn1_NOVALUE | Rest], MapAcc) ->
+    encode_jer_component(CompInfos, Rest, MapAcc);
+encode_jer_component([{_Name, _Type, {'DEFAULT',_}} | CompInfos], [asn1_DEFAULT | Rest], MapAcc) ->
+    encode_jer_component(CompInfos, Rest, MapAcc);
+encode_jer_component([{Name, Type, _OptOrDefault} | CompInfos], [Value | Rest], MapAcc) ->
+    Enc = encode_jer(Type, Value),
+    encode_jer_component(CompInfos, Rest, MapAcc#{Name => Enc});
+encode_jer_component([], _, MapAcc) ->
+    MapAcc.
+
+decode_jer(Module,InfoFunc,Val) ->
+    Info = Module:InfoFunc(),
+    decode_jer(Info,Val).
+%% FIXME probably generate EnumList as a map with binaries as keys
+%% and check if the Value is in the map. Also take the extensionmarker into
+%% account and in that case allow any value but return as binary since it
+%% is a potential atom leak to convert unknown values to atoms
+%% maybe convert to existing atom
+%% FIXME this is a discrepancy compare with other backends which return {asn1_enum,Val}
+%% for unknown enum values when the type is extensible
+decode_jer({'ENUMERATED',_EnumList}, Val) when is_binary(Val) ->
+    binary_to_existing_atom(Val,utf8);
+decode_jer({'ENUMERATED',_EnumList}, Val) when is_boolean(Val) ->
+    Val;
+decode_jer({'ENUMERATED',_EnumList}, null) ->
+    null;
+decode_jer({Type = {'ENUMERATED',_EnumList},_Constr}, Val) ->
+    decode_jer(Type,Val);
+decode_jer({'ENUMERATED_EXT',EnumList}, Val) ->
+    decode_jer({'ENUMERATED',EnumList}, Val);
+decode_jer({Type = {'ENUMERATED_EXT',_EnumList},_Constr}, Val) ->
+    decode_jer(Type,Val);
+
+decode_jer({typeinfo,{Module,Func}},Val) ->
+    TypeInfo = Module:Func(),
+    decode_jer(TypeInfo,Val); 
+decode_jer({sequence,Sname,_Arity,CompInfos},Value) 
+  when is_map(Value) ->    
+    DecodedComps = decode_jer_component(CompInfos,Value,[]),
+    list_to_tuple([Sname|DecodedComps]);
+
+%% Unfortunately we have to represent strings as lists to be compatible 
+%% with the other backends. Should add an option to the compiler in the future
+%% which makes it possible to represent all strings as erlang binaries
+decode_jer(string,Str) when is_binary(Str) ->
+    binary_to_list(Str);
+decode_jer({string,_Prop},Str) when is_binary(Str) ->
+    binary_to_list(Str);
+decode_jer('INTEGER',Int) when is_integer(Int) ->
+    Int;
+decode_jer({Type = {'INTEGER_NNL',_NNList},_},Int) ->
+    decode_jer(Type,Int);
+decode_jer({'INTEGER_NNL',NNList},Int) ->
+    case lists:keyfind(Int, 2, NNList) of
+        {NewName, _} ->
+            NewName;
+        _ ->
+            Int
+    end;
+decode_jer({'INTEGER',_Prop},Int) when is_integer(Int) ->
+    Int;
+decode_jer('BOOLEAN',Bool) when is_boolean(Bool) ->
+    Bool;
+decode_jer({'BOOLEAN',_Prop},Bool) when is_boolean(Bool) ->
+    Bool;
+decode_jer('NULL',null) ->
+    'NULL';
+decode_jer(legacy_octet_string,Str) when is_binary(Str) ->
+    json2octetstring2string(binary_to_list(Str));
+decode_jer(octet_string,Str) when is_binary(Str) ->
+    json2octetstring2binary(binary_to_list(Str));
+decode_jer({sof,Type},Vals) when is_list(Vals) ->
+    [decode_jer(Type,Val)||Val <- Vals];
+decode_jer({choice,ChoiceTypes},ChoiceVal) ->
+    [{Alt,Val}] = maps:to_list(ChoiceVal),
+    case ChoiceTypes of
+        #{Alt := Type} ->
+            Type = maps:get(Alt,ChoiceTypes),
+            {binary_to_atom(Alt,utf8),decode_jer(Type,Val)};
+        _ ->
+            exit({error,{asn1,{invalid_choice,Alt,maps:keys(ChoiceTypes)}}})
+    end;
+decode_jer(bit_string,#{<<"value">> := Str, <<"length">> := Length}) ->
+    json2bitstring(binary_to_list(Str),Length);
+decode_jer({bit_string,FixedLength},Str) when is_binary(Str) ->
+    json2bitstring(binary_to_list(Str),FixedLength);
+decode_jer({bit_string_nnl,NNL},#{<<"value">> := Str, <<"length">> := Length}) -> 
+    BitStr = json2bitstring(binary_to_list(Str),Length),
+    jer_bitstr2names(BitStr,NNL);
+decode_jer({{bit_string_nnl,NNL},FixedLength},Str) when is_binary(Str)->
+    BitStr = json2bitstring(binary_to_list(Str),FixedLength),
+    jer_bitstr2names(BitStr,NNL);
+decode_jer({compact_bit_string_nnl,NNL},Value) ->
+    decode_jer({bit_string_nnl,NNL},Value);
+decode_jer({{compact_bit_string_nnl,NNL},FixedLength},Value) ->
+    decode_jer({{bit_string_nnl,NNL},FixedLength},Value);
+decode_jer(compact_bit_string,#{<<"value">> := Str, <<"length">> := Length}) ->
+    BitStr = json2bitstring(binary_to_list(Str),Length),
+    jer_bitstr2compact(BitStr);
+decode_jer({compact_bit_string,FixedLength},Str) ->
+    BitStr = json2bitstring(binary_to_list(Str),FixedLength),
+    Unused = (8 - (FixedLength rem 8)) band 7,
+    {Unused,<<BitStr/bitstring,0:Unused>>};
+decode_jer('OBJECT IDENTIFIER',OidBin) when is_binary(OidBin) ->
+    json2oid(OidBin);
+decode_jer('RELATIVE-OID',OidBin) when is_binary(OidBin) ->
+    json2oid(OidBin);
+decode_jer({'ObjClassFieldType',_,_},Bin) when is_binary(Bin) ->
+    Bin;
+decode_jer('ASN1_OPEN_TYPE',Bin) when is_binary(Bin) ->
+    Bin.
+
+decode_jer_component([{Name, Type, _OptOrDefault} | CompInfos], VMap, Acc)
+    when is_map_key(Name, VMap) ->
+    Value = maps:get(Name, VMap),
+    Dec = decode_jer(Type, Value),
+    decode_jer_component(CompInfos, VMap, [Dec | Acc]);
+decode_jer_component([{_Name, _Type, 'OPTIONAL'} | CompInfos], VMap, Acc) ->
+    decode_jer_component(CompInfos, VMap, [asn1_NOVALUE | Acc]);
+decode_jer_component([{_Name, _Type, {'DEFAULT',Dvalue}} | CompInfos], VMap, Acc) ->
+    decode_jer_component(CompInfos, VMap, [Dvalue | Acc]);
+decode_jer_component([{Name, _Type, _OptOrDefault} | _CompInfos], VMap, _Acc) ->
+    exit({error,{asn1,{{decode,{mandatory_component_missing,Name}},VMap}}});
+decode_jer_component([], _, Acc) ->
+    lists:reverse(Acc).
+
+%% This is the default representation of octet string i.e binary
+json2octetstring2binary(Value) ->
+    list_to_binary(json2octetstring(Value,[])).
+
+%% This is the legacy_types representation of octet string i.e as a list
+json2octetstring2string(Value) ->
+    json2octetstring(Value,[]).
+
+json2octetstring([A1,A2|Rest],Acc) ->
+    Int = list_to_integer([A1,A2],16),
+    json2octetstring(Rest,[Int|Acc]);
+json2octetstring([], Acc) ->
+    lists:reverse(Acc).
+
+json2bitstring(Value,Length) ->
+    json2bitstring(Value,Length,[]).
+
+json2bitstring([A1,A2],Length,Acc) ->
+    Int = list_to_integer([A1,A2],16) bsr (8-Length),
+    Bin = list_to_binary(lists:reverse(Acc)),
+    << Bin/binary,Int:Length>>;
+json2bitstring([A1,A2|Rest],Length,Acc) ->
+    Int = list_to_integer([A1,A2],16),
+    json2bitstring(Rest,Length-8,[Int|Acc]);
+json2bitstring([],0,Acc) ->
+    Bin = list_to_binary(lists:reverse(Acc)),
+    Bin.
+
+bitstring2json(BitStr) when is_binary(BitStr) ->
+    octetstring2json(binary_to_list(BitStr));
+bitstring2json(BitStr) ->
+    Pad = 8 - bit_size(BitStr) rem 8,
+    NewStr = <<BitStr/bitstring,0:Pad>>,
+    octetstring2json(binary_to_list(NewStr)).
+
+octetstring2json(List) when is_list(List) ->
+    list_to_binary([begin Num = integer_to_list(X,16), 
+           if length(Num) == 1 -> "0"++Num;
+              true -> Num
+           end 
+     end|| X<-List]).
+
+oid2json(Oid) when is_tuple(Oid) ->
+    OidList = tuple_to_list(Oid),
+    OidNumberStr = [integer_to_list(V)|| V <- OidList],
+    oid2json(OidNumberStr,[]).
+
+oid2json([Num|T],[]) ->
+    oid2json(T,[Num]);
+oid2json([Num|T],Acc) ->
+    oid2json(T,[Num,$.|Acc]);
+oid2json([],Acc) ->
+    list_to_binary(lists:reverse(Acc)).
+
+json2oid(OidStr) when is_binary(OidStr) ->
+    OidList = binary:split(OidStr,[<<".">>],[global]),
+    OidNumList = [binary_to_integer(Num)||Num <- OidList],
+    list_to_tuple(OidNumList).
+
+jer_bit_str2bitstr(Compact = {_Unused,_Binary}, _NamedBitList) ->
+    jer_compact2bitstr(Compact);
+jer_bit_str2bitstr(Int, _NamedBitList) when is_integer(Int) ->
+    jer_compact2bitstr(Int);
+jer_bit_str2bitstr(BitList = [Bit|_], _NamedBitList) when Bit == 1; Bit == 0 ->
+    Int = list_to_integer([case B of 0 -> $0; 1 -> $1 end || B <- BitList],2),
+    Len = length(BitList),
+    <<Int:Len>>;
+jer_bit_str2bitstr([H | _] = Bits, NamedBitList)
+    when is_atom(H) ->
+    jer_do_encode_named_bit_string(Bits, NamedBitList);
+jer_bit_str2bitstr([{bit, _} | _] = Bits, NamedBitList) ->
+    jer_do_encode_named_bit_string(Bits, NamedBitList);
+jer_bit_str2bitstr([], _NamedBitList) ->
+    <<>>;
+jer_bit_str2bitstr(BitStr,_NamedBitList) when is_bitstring(BitStr) ->
+    BitStr.
+
+jer_compact2bitstr({Unused,Binary}) ->
+    Size = bit_size(Binary) - Unused,
+    <<BitStr:Size/bitstring,_/bitstring >> = Binary,
+    BitStr;
+jer_compact2bitstr(Int) when is_integer(Int) ->
+    jer_int2bitstr(Int);
+jer_compact2bitstr(BitList = [Bit|_]) when Bit == 1; Bit == 0 ->
+    IntStr = jer_skip_trailing_zeroes(BitList,[]),
+    Int = list_to_integer(IntStr,2),
+    Len = length(IntStr),
+    <<Int:Len>>.
+
+jer_skip_trailing_zeroes([1|Rest],Acc) ->
+    jer_skip_trailing_zeroes(Rest,[$1|Acc]);
+jer_skip_trailing_zeroes([0|Rest],Acc) ->
+    jer_skip_trailing_zeroes(Rest,[$0|Acc]);
+jer_skip_trailing_zeroes([],[$0|Acc]) ->
+    jer_skip_trailing_zeroes([],Acc);
+jer_skip_trailing_zeroes([],Acc) ->
+    lists:reverse(Acc).
+
+
+    
+
+jer_padbitstr(BitStr,FixedLength) when bit_size(BitStr) == FixedLength ->
+    BitStr;
+jer_padbitstr(BitStr,FixedLength) when bit_size(BitStr) < FixedLength ->
+    Len = bit_size(BitStr),
+    PadLen = FixedLength - Len,
+    <<BitStr/bitstring,0:PadLen>>.
+
+jer_int2bitstr(Int) when is_integer(Int), Int >= 0 ->
+    jer_int2bitstr(Int,<<>>).
+
+jer_int2bitstr(0,Acc) ->
+    Acc;
+jer_int2bitstr(Int,Acc) ->
+    Bit = Int band 1,
+    jer_int2bitstr(Int bsr 1,<<Acc/bitstring,Bit:1>>).
+    
+jer_bitstr2compact(BitStr) ->
+    Size = bit_size(BitStr),
+    Unused = (8 - Size rem 8) band 7,
+    {Unused,<<BitStr/bitstring,0:Unused>>}.
+
+jer_do_encode_named_bit_string([FirstVal | RestVal], NamedBitList) ->
+    ToSetPos = jer_get_all_bitposes([FirstVal | RestVal], NamedBitList, []),
+    Size = lists:max(ToSetPos) + 1,
+    BitList = jer_make_and_set_list(Size, ToSetPos, 0),
+    encode_bitstring(BitList).
+
+jer_get_all_bitposes([{bit, ValPos} | Rest], NamedBitList, Ack) ->
+    jer_get_all_bitposes(Rest, NamedBitList, [ValPos | Ack]);
+jer_get_all_bitposes([Val | Rest], NamedBitList, Ack) when is_atom(Val) ->
+    case lists:keyfind(Val, 1, NamedBitList) of
+        {_ValName, ValPos} ->
+            jer_get_all_bitposes(Rest, NamedBitList, [ValPos | Ack]);
+        _ ->
+            exit({error, {asn1, {bitstring_namedbit, Val}}})
+    end;
+jer_get_all_bitposes([], _NamedBitList, Ack) ->
+    lists:sort(Ack).
+
+jer_make_and_set_list(0, [], _) ->
+    [];
+jer_make_and_set_list(0, _, _) ->
+    exit({error, {asn1, bitstring_sizeconstraint}});
+jer_make_and_set_list(Len, [XPos | SetPos], XPos) ->
+    [1 | jer_make_and_set_list(Len - 1, SetPos, XPos + 1)];
+jer_make_and_set_list(Len, [Pos | SetPos], XPos) ->
+    [0 | jer_make_and_set_list(Len - 1, [Pos | SetPos], XPos + 1)];
+jer_make_and_set_list(Len, [], XPos) ->
+    [0 | jer_make_and_set_list(Len - 1, [], XPos + 1)].
+
+%%=================================================================
+%% Do the actual encoding
+%%     ([bitlist]) -> {ListLen, UnusedBits, OctetList}
+%%=================================================================
+
+encode_bitstring([B8, B7, B6, B5, B4, B3, B2, B1 | Rest]) ->
+    Val = (B8 bsl 7) bor (B7 bsl 6) bor (B6 bsl 5) bor (B5 bsl 4) bor
+	(B4 bsl 3) bor (B3 bsl 2) bor (B2 bsl 1) bor B1,
+    encode_bitstring(Rest, <<Val>>);
+encode_bitstring(Val) ->
+    unused_bitlist(Val, <<>>).
+
+encode_bitstring([B8, B7, B6, B5, B4, B3, B2, B1 | Rest], Ack) ->
+    Val = (B8 bsl 7) bor (B7 bsl 6) bor (B6 bsl 5) bor (B5 bsl 4) bor
+	(B4 bsl 3) bor (B3 bsl 2) bor (B2 bsl 1) bor B1,
+    encode_bitstring(Rest, [Ack | [Val]]);
+%%even multiple of 8 bits..
+encode_bitstring([], Ack) ->
+    Ack;
+%% unused bits in last octet
+encode_bitstring(Rest, Ack) ->
+    unused_bitlist(Rest,Ack).
+
+%%%%%%%%%%%%%%%%%%
+%% unused_bitlist([list of ones and zeros <= 7], 7, []) ->
+%%  {Unused bits, Last octet with bits moved to right}
+unused_bitlist([], Ack) ->
+    Ack;
+unused_bitlist([Bit | Rest], Ack) ->
+    unused_bitlist(Rest, <<Ack/bitstring,Bit:1>>).
+
+jer_bitstr2names(BitStr,[]) ->
+    BitStr;
+jer_bitstr2names(BitStr,NNL) ->
+    %% Fixme, the sorting should be done in compile time, maybe it already is
+    SortedList  = lists:keysort(2,NNL), %% Should be from bit 0 to bit N
+    jer_bitstr2names(BitStr,SortedList,0,[]).
+
+jer_bitstr2names(<<1:1,BitStr/bitstring>>,[{Name,Pos}|Rest],Pos,Acc) ->
+    jer_bitstr2names(BitStr,Rest,Pos+1,[Name|Acc]);
+jer_bitstr2names(<<1:1,BitStr/bitstring>>,NNL,Num,Acc) ->
+    jer_bitstr2names(BitStr,NNL,Num+1,[{bit,Num}|Acc]);
+jer_bitstr2names(<<0:1,BitStr/bitstring>>,[{_,Num}|Rest],Num,Acc) ->
+    jer_bitstr2names(BitStr,Rest,Num+1,Acc);
+jer_bitstr2names(<<0:1,BitStr/bitstring>>,NNL,Num,Acc) ->
+    jer_bitstr2names(BitStr,NNL,Num+1,Acc);
+jer_bitstr2names(<<>>,_,_,Acc) ->
+    lists:reverse(Acc).
+
+
+    
+
+    
+    
diff --git a/lib/asn1/test/asn1_SUITE.erl b/lib/asn1/test/asn1_SUITE.erl
index 70c70208e4..f148dfc5ce 100644
--- a/lib/asn1/test/asn1_SUITE.erl
+++ b/lib/asn1/test/asn1_SUITE.erl
@@ -219,9 +219,17 @@ end_per_testcase(_Func, Config) ->
 %%------------------------------------------------------------------------------
 
 test(Config, TestF) ->
+    TestJer = case code:which(jsx) of
+                  non_existing -> [];
+                  _ -> [jer]
+              end,
     test(Config, TestF, [per,
                          uper,
-                         ber]).
+                         ber] ++ TestJer),
+    case TestJer of
+        [] -> {comment,"skipped JER"};
+        _ -> ok
+    end.
 
 test(Config, TestF, Rules) ->
     Fun = fun(C, R, O) ->
@@ -314,7 +322,7 @@ do_test_prim(Rule, NoOkWrapper) ->
     testPrim:obj_id(Rule),
     testPrim:rel_oid(Rule),
     testPrim:null(Rule),
-    testPrim:real(Rule).
+    Rule =/= jer andalso testPrim:real(Rule). %% Temporary workaround for JER
 
 testCompactBitString(Config) -> test(Config, fun testCompactBitString/3).
 testCompactBitString(Config, Rule, Opts) ->
@@ -388,7 +396,7 @@ testExtensibilityImplied(Config) ->
 testExtensibilityImplied(Config, Rule, Opts) ->
     asn1_test_lib:compile("ExtensibilityImplied", Config,
 			  [Rule,no_ok_wrapper|Opts]),
-    testExtensibilityImplied:main().
+    testExtensibilityImplied:main(Rule).
 
 testChoice(Config) -> test(Config, fun testChoice/3).
 testChoice(Config, Rule, Opts) ->
@@ -812,6 +820,7 @@ testConstraints(Config, Rule, Opts) ->
     testConstraints:int_constraints(Rule),
     case Rule of
 	ber -> ok;
+        jer -> ok; % subtype constraint is not checked
 	_ -> testConstraints:refed_NNL_name(Rule)
     end.
 
@@ -849,7 +858,7 @@ testUniqueObjectSets(Config, Rule, Opts) ->
 testInfObjExtract(Config) -> test(Config, fun testInfObjExtract/3).
 testInfObjExtract(Config, Rule, Opts) ->
     asn1_test_lib:compile("InfObjExtract", Config, [Rule|Opts]),
-    testInfObjExtract:main().
+    testInfObjExtract:main(Rule).
 
 testParam(Config) ->
     test(Config, fun testParam/3, [ber,{ber,[der]},per,uper]).
@@ -877,6 +886,7 @@ testMergeCompile(Config, Rule, Opts) ->
     testMergeCompile:mvrasn(Rule).
 
 testobj(Config) -> test(Config, fun testobj/3).
+testobj(_Config, jer, _Opts) -> ok;
 testobj(Config, Rule, Opts) ->
     asn1_test_lib:compile("RANAP", Config, [legacy_erlang_types,
 					    Rule|Opts]),
@@ -897,7 +907,7 @@ testImport(Config, Rule, Opts) ->
 	     "Importing","Exporting"],
     asn1_test_lib:compile_all(Files, Config, [Rule|Opts]),
     42 = 'ImportsFrom':i(),
-    testImporting:main(),
+    testImporting:main(Rule),
     ok.
 
 testMegaco(Config) -> test(Config, fun testMegaco/3).
@@ -917,7 +927,7 @@ testContextSwitchingTypes(Config) ->
     test(Config, fun testContextSwitchingTypes/3).
 testContextSwitchingTypes(Config, Rule, Opts) ->
     asn1_test_lib:compile("ContextSwitchingTypes", Config, [Rule|Opts]),
-    testContextSwitchingTypes:test(Config).
+    testContextSwitchingTypes:test(Rule,Config).
 
 testTypeValueNotation(Config) -> test(Config, fun testTypeValueNotation/3).
 testTypeValueNotation(Config, Rule, Opts) ->
@@ -1025,6 +1035,8 @@ testNortel(Config, Rule, Opts) ->
     asn1_test_lib:compile("Nortel", Config, [Rule|Opts]).
 
 test_undecoded_rest(Config) -> test(Config, fun test_undecoded_rest/3).
+test_undecoded_rest(_Config,jer,_Opts) ->
+    ok; % not relevant for JER
 test_undecoded_rest(Config, Rule, Opts) ->
     do_test_undecoded_rest(Config, Rule, Opts),
     do_test_undecoded_rest(Config, Rule, [no_ok_wrapper|Opts]),
@@ -1065,7 +1077,9 @@ testS1AP(Config, Rule, Opts) ->
 	uper ->
 	    ok;
 	ber ->
-	    ok
+	    ok;
+        jer ->
+            ok
     end.
 
 testRfcs() ->
diff --git a/lib/asn1/test/asn1_SUITE_data/InfClass.asn b/lib/asn1/test/asn1_SUITE_data/InfClass.asn
index ecc6764402..bd021a9e23 100644
--- a/lib/asn1/test/asn1_SUITE_data/InfClass.asn
+++ b/lib/asn1/test/asn1_SUITE_data/InfClass.asn
@@ -27,7 +27,7 @@ OTHER-FUNCTION ::= CLASS {
 ObjSet1 FUNCTION ::= { ... }
 
 val1 FUNCTION ::= {
-    &ArgumentType  INTEGER,
+    &ArgumentType  INTEGER (1..255),
     &ResultType    INTEGER,
     &code          3
     }
@@ -45,7 +45,9 @@ ObjSet2 FUNCTION ::= {
 
 
 -- added for OTP-4591
-
+ArgumentType ::= INTEGER
+ResultType ::= INTEGER
+    
 Seq ::= SEQUENCE {
   arg  FUNCTION.&ArgumentType ({ObjSet2}{@val1}),
   res  FUNCTION.&ResultType   ({ObjSet2}{@val1}),
diff --git a/lib/asn1/test/asn1_SUITE_data/extensionAdditionGroup.erl b/lib/asn1/test/asn1_SUITE_data/extensionAdditionGroup.erl
index cd6c74b995..e0639ddf89 100644
--- a/lib/asn1/test/asn1_SUITE_data/extensionAdditionGroup.erl
+++ b/lib/asn1/test/asn1_SUITE_data/extensionAdditionGroup.erl
@@ -43,7 +43,8 @@ run(Erule) ->
 %% From X.691 (07/2002) A.4.
 encoded_ax(per) ->  "9E000180 010291A4";
 encoded_ax(uper) -> "9E000600 040A4690";
-encoded_ax(ber) ->  none.
+encoded_ax(ber) -> none;
+encoded_ax(jer) -> none. 
 
 hex_to_binary(none) ->
     none;
diff --git a/lib/asn1/test/asn1_app_SUITE.erl b/lib/asn1/test/asn1_app_SUITE.erl
index b06eb59ed9..55b5b40737 100644
--- a/lib/asn1/test/asn1_app_SUITE.erl
+++ b/lib/asn1/test/asn1_app_SUITE.erl
@@ -133,7 +133,7 @@ check_asn1ct_modules(Extra) ->
 		  asn1ct_gen_ber_bin_v2,asn1ct_value,
 		  asn1ct_tok,asn1ct_parser2,asn1ct_table,
 		  asn1ct_imm,asn1ct_func,asn1ct_rtt,
-		  asn1ct_eval_ext],
+		  asn1ct_eval_ext,asn1ct_gen_jer],
     case Extra -- ASN1CTMods of
 	[] ->
 	    ok;
diff --git a/lib/asn1/test/asn1_test_lib.erl b/lib/asn1/test/asn1_test_lib.erl
index 1cc332406b..af8462f0c9 100644
--- a/lib/asn1/test/asn1_test_lib.erl
+++ b/lib/asn1/test/asn1_test_lib.erl
@@ -109,7 +109,7 @@ compile_file(File, Options0) ->
 compile_maps(File, Options) ->
     unload_map_mod(File),
     Incompat = [abs,compact_bit_string,legacy_bit_string,
-                legacy_erlang_types,maps,asn1_test_lib_no_maps],
+                legacy_erlang_types,maps,asn1_test_lib_no_maps,jer],
     case lists:any(fun(E) -> lists:member(E, Incompat) end, Options) of
         true ->
             ok;
diff --git a/lib/asn1/test/testChoPrim.erl b/lib/asn1/test/testChoPrim.erl
index 91fbc1488a..6ee8df1d6a 100644
--- a/lib/asn1/test/testChoPrim.erl
+++ b/lib/asn1/test/testChoPrim.erl
@@ -38,7 +38,9 @@ bool(Rules) ->
 	per ->
 	    ok;
 	uper ->
-	    ok
+	    ok;
+        jer ->
+            ok
     end,
     ok.
 
@@ -58,7 +60,9 @@ int(Rules) ->
 	per ->
 	    ok;
 	uper ->
-	    ok
+	    ok;
+        jer ->
+            ok
     end,
     ok.
 
diff --git a/lib/asn1/test/testCompactBitString.erl b/lib/asn1/test/testCompactBitString.erl
index 319ecc1a59..7241c90e00 100644
--- a/lib/asn1/test/testCompactBitString.erl
+++ b/lib/asn1/test/testCompactBitString.erl
@@ -40,10 +40,10 @@ compact_bit_string(Rules) ->
 	      {0,<<75,80,248,215,49,149,42,213>>}),
 
     roundtrip('Bs1', [1,1,1,1,1,1,1,1], {0,<<255>>}),
-    roundtrip('Bs1', [0,1,0,0,1,0], {2,<<16#48>>}),
-    roundtrip('Bs1', [1,0,0,0,0,0,0,0,0], {7,<<16#80,0>>}),
-    roundtrip('Bs1', [0,1,0,0,1,0,1,1,1,1,1,0,0,0,1,0,0,1,1],
-	      {5,<<75,226,96>>}),
+
+    (Rules =/= jer) andalso roundtrip('Bs1', [0,1,0,0,1,0], {2,<<16#48>>}),
+    (Rules =/= jer) andalso roundtrip('Bs1', [1,0,0,0,0,0,0,0,0], {7,<<16#80,0>>}),
+    roundtrip('Bs1', [0,1,0,0,1,0,1,1,1,1,1,0,0,0,1,0,0,1,1], {5,<<75,226,96>>}),
     
     case Rules of
 	ber ->
@@ -75,7 +75,7 @@ compact_bit_string(Rules) ->
     %%==========================================================
     
     roundtrip('Bs3', [mo,tu,fr]),
-    roundtrip('Bs3', [0,1,1,0,0,1,0], [mo,tu,fr]),
+    (Rules =/= jer) andalso roundtrip('Bs3', [0,1,1,0,0,1,0], [mo,tu,fr]),
     
     %%==========================================================
     %% BsPri ::= [PRIVATE 61] BIT STRING
@@ -128,6 +128,7 @@ ticket_7734(_) ->
     BS = {0,list_to_binary(lists:duplicate(128, 0))},
     roundtrip('BS1024', BS).
 
+bit_string_unnamed(jer) -> ok;
 bit_string_unnamed(_Rules) ->
     roundtrip('TransportLayerAddress', [0,1,1,0], {4,<<96>>}).
 
diff --git a/lib/asn1/test/testConstraints.erl b/lib/asn1/test/testConstraints.erl
index 6a1fbe4f73..4611bbe2cf 100644
--- a/lib/asn1/test/testConstraints.erl
+++ b/lib/asn1/test/testConstraints.erl
@@ -143,12 +143,12 @@ int_constraints(Rules) ->
     v_roundtrip(Rules, 'Sv2', 2),
     v_roundtrip(Rules, 'Sv2', 3),
     v_roundtrip(Rules, 'Sv2', 17),
-
+    
     %% Encoded as extension
     v_roundtrip(Rules, 'Sv2', 1),
     v_roundtrip(Rules, 'Sv2', 4),
     v_roundtrip(Rules, 'Sv2', 18),
-
+    
     %% Encoded as root
     v_roundtrip(Rules, 'Sv3', a),
     v_roundtrip(Rules, 'Sv3', b),
@@ -156,7 +156,7 @@ int_constraints(Rules) ->
     v_roundtrip(Rules, 'Sv3', 2, a),
     v_roundtrip(Rules, 'Sv3', 3, b),
     v_roundtrip(Rules, 'Sv3', 17, z),
-
+    
     %% Encoded as extension
     v_roundtrip(Rules, 'Sv3', 1),
     v_roundtrip(Rules, 'Sv3', 4),
@@ -295,16 +295,19 @@ v(Rule, 'Sv3', Val) when is_integer(Val) -> v(Rule, 'Sv2', Val).
 
 shorter_ext(per, "a") -> <<16#80,16#01,16#61>>;
 shorter_ext(uper, "a") -> <<16#80,16#E1>>;
-shorter_ext(ber, _) -> none.
+shorter_ext(ber, _) -> none;
+shorter_ext(jer, _) -> none.
 
 refed_NNL_name(_Erule) ->
     roundtrip('AnotherThing', fred),
     {error,_Reason} = 'Constraints':encode('AnotherThing', fred3).
 
+v_roundtrip(jer,_,_) -> ok;
 v_roundtrip(Erule, Type, Value) ->
     Encoded = asn1_test_lib:hex_to_bin(v(Erule, Type, Value)),
     Encoded = roundtrip('Constraints', Type, Value).
 
+v_roundtrip(jer,_,_,_) -> ok;
 v_roundtrip(Erule, Type, Value, Expected) ->
     Encoded = asn1_test_lib:hex_to_bin(v(Erule, Type, Value)),
     Encoded = asn1_test_lib:roundtrip_enc('Constraints', Type, Value, Expected).
@@ -328,7 +331,7 @@ range_error(ber, Type, Value) ->
     {ok,Encoded} = 'Constraints':encode(Type, Value),
     {error,{asn1,_}} = 'Constraints':decode(Type, Encoded),
     ok;
-range_error(Per, Type, Value) when Per =:= per; Per =:= uper ->
+range_error(Per, Type, Value) when Per =:= per; Per =:= uper; Per =:= jer ->
     %% (U)PER: Values outside the effective range should be rejected
     %% on encode.
     {error,_} = 'Constraints':encode(Type, Value),
diff --git a/lib/asn1/test/testContextSwitchingTypes.erl b/lib/asn1/test/testContextSwitchingTypes.erl
index bc7d9733b9..36a61457e6 100644
--- a/lib/asn1/test/testContextSwitchingTypes.erl
+++ b/lib/asn1/test/testContextSwitchingTypes.erl
@@ -20,11 +20,12 @@
 %%
 -module(testContextSwitchingTypes).
 
--export([test/1]).
+-export([test/2]).
 
 -include_lib("common_test/include/ct.hrl").
 
-test(Config) ->
+test(jer,_Config) -> ok;
+test(_Rule,Config) ->
     ValT_1 = 'ContextSwitchingTypes':'val1-T'(),
     check_EXTERNAL(enc_dec('T', ValT_1)),
 
diff --git a/lib/asn1/test/testDeepTConstr.erl b/lib/asn1/test/testDeepTConstr.erl
index 9169cf5953..565abea5af 100644
--- a/lib/asn1/test/testDeepTConstr.erl
+++ b/lib/asn1/test/testDeepTConstr.erl
@@ -26,6 +26,7 @@
 
 -include_lib("common_test/include/ct.hrl").
 
+main(jer) -> ok; % Table constraints not JER visible
 main(_Erule) ->
     Val1 = {substrings,
 	    {'FilterItem_substrings',
diff --git a/lib/asn1/test/testEnumExt.erl b/lib/asn1/test/testEnumExt.erl
index 0f8ca816d4..b30750f7fc 100644
--- a/lib/asn1/test/testEnumExt.erl
+++ b/lib/asn1/test/testEnumExt.erl
@@ -40,14 +40,17 @@ main(Rule) when Rule =:= per; Rule =:= uper ->
     B64 = <<64>>,
     B64 = roundtrip('Noext', red),
     common(Rule);
-main(ber) ->
+main(Rule) when Rule =:= ber; Rule =:= jer ->
     io:format("main(ber)~n",[]),
     %% ENUMERATED with extensionmark (value is in root set)
     roundtrip('Ext', red),
 
     %% value is an extensionvalue
     {ok,Bytes1_1} = 'EnumExt':encode('Ext1', orange),
-    {ok,{asn1_enum,7}} = 'EnumExt':decode('Ext', Bytes1_1),
+    case {Rule,'EnumExt':decode('Ext', Bytes1_1)} of
+        {ber,{ok,{asn1_enum,7}}} -> ok;
+        {jer,{ok,orange}} -> ok
+    end,
 
     %% ENUMERATED no extensionmark
     roundtrip('Noext', red),
@@ -57,12 +60,9 @@ main(ber) ->
     roundtrip('Globalstate', preop),
     roundtrip('Globalstate', com),
 
-    common(ber).
+    common(Rule).
 
 common(Erule) ->
-    roundtrip('SubExt1', blue),
-    roundtrip('SubExt1', orange),
-    roundtrip('SubExt1', black),
 
     roundtrip('Seq', {'Seq',blue,42}),
     roundtrip('Seq', {'Seq',red,42}),
@@ -82,11 +82,16 @@ common(Erule) ->
 
     v_roundtrip(Erule, 'EnumSkip', d),
 
+    roundtrip('SubExt1', blue),
+    roundtrip('SubExt1', orange),
+    roundtrip('SubExt1', black),
+
     ok.
 
 roundtrip(Type, Value) ->
     asn1_test_lib:roundtrip_enc('EnumExt', Type, Value).
 
+v_roundtrip(jer, _Type, _Value) -> ok;
 v_roundtrip(Erule, Type, Value) ->
     Encoded = roundtrip(Type, Value),
     Encoded = asn1_test_lib:hex_to_bin(v(Erule, Type, Value)).
diff --git a/lib/asn1/test/testExtensibilityImplied.erl b/lib/asn1/test/testExtensibilityImplied.erl
index 3b2e021c48..00729e6a8b 100644
--- a/lib/asn1/test/testExtensibilityImplied.erl
+++ b/lib/asn1/test/testExtensibilityImplied.erl
@@ -20,11 +20,16 @@
 %%
 
 -module(testExtensibilityImplied).
--export([main/0]).
+-export([main/1]).
 
-main() ->
+main(Rule) ->
     M = 'ExtensibilityImplied',
     {'Seq2',true} = M:decode('Seq2', M:encode('Seq1', {'Seq1',true,42})),
     {'Set2',true} = M:decode('Set2', M:encode('Set1', {'Set1',true,42})),
-    {asn1_enum,_} = M:decode('Enum2', M:encode('Enum1', ext)),
+    case Rule of
+        jer ->
+            ext = M:decode('Enum2', M:encode('Enum1', ext));
+        _ ->
+            {asn1_enum,_} = M:decode('Enum2', M:encode('Enum1', ext))
+    end,
     ok.
diff --git a/lib/asn1/test/testExtensionDefault.erl b/lib/asn1/test/testExtensionDefault.erl
index cc50fa95b8..d5da5d7c83 100644
--- a/lib/asn1/test/testExtensionDefault.erl
+++ b/lib/asn1/test/testExtensionDefault.erl
@@ -22,14 +22,17 @@
 
 -export([main/1]).
 
-main(_Erule) ->
+main(Erule) ->
     roundtrip('Message', {'Message',1,low}),    %Will be explicitly encoded.
     roundtrip('Message', {'Message',1,high}),
     roundtrip('Message', {'Message',1,asn1_DEFAULT}, {'Message',1,low}),
-
-    map_roundtrip('Message', #{id=>1,priority=>low}), %Will be explicitly encoded.
-    map_roundtrip('Message', #{id=>1,priority=>high}),
-    map_roundtrip('Message', #{id=>1}, #{id=>1,priority=>low}),
+    case Erule of
+        jer -> ok; % no support for maps right now
+        _ ->
+            map_roundtrip('Message', #{id=>1,priority=>low}), %Will be explicitly encoded.
+            map_roundtrip('Message', #{id=>1,priority=>high}),
+            map_roundtrip('Message', #{id=>1}, #{id=>1,priority=>low})
+    end,
     ok.
 
 roundtrip(Type, Value) ->
diff --git a/lib/asn1/test/testFragmented.erl b/lib/asn1/test/testFragmented.erl
index 59e5c99c61..04eeda2281 100644
--- a/lib/asn1/test/testFragmented.erl
+++ b/lib/asn1/test/testFragmented.erl
@@ -22,6 +22,7 @@
 
 -export([main/1]).
 
+main(jer) -> ok;
 main(_Erule) ->
     roundtrip('PDU', {'PDU',1,false,[<<"abc">>,<<"def">>]}),
     B256 = lists:seq(0, 255),
diff --git a/lib/asn1/test/testINSTANCE_OF.erl b/lib/asn1/test/testINSTANCE_OF.erl
index aceaaf7a1d..0c63269892 100644
--- a/lib/asn1/test/testINSTANCE_OF.erl
+++ b/lib/asn1/test/testINSTANCE_OF.erl
@@ -23,19 +23,23 @@
 
 -include_lib("common_test/include/ct.hrl").
 
-main(_Erule) ->
+main(Erule) ->
     Int = roundtrip('Int', 3),
 
     ValotherName = {otherName,{'INSTANCE OF',{2,4},Int}},
     _ = roundtrip('GeneralName', ValotherName),
 
-    VallastName1 = {lastName,{'GeneralName_lastName',{2,4},12}},
-    _ = roundtrip('GeneralName', VallastName1),
-
-    VallastName2 = {lastName,{'GeneralName_lastName',{2,3,4},
-			      {'Seq',12,true}}},
-    _ = roundtrip('GeneralName', VallastName2),
-    ok.
+    case Erule of
+        jer -> ok;
+        _ ->
+            VallastName1 = {lastName,{'GeneralName_lastName',{2,4},12}},
+            _ = roundtrip('GeneralName', VallastName1),
+            
+            VallastName2 = {lastName,{'GeneralName_lastName',{2,3,4},
+                                      {'Seq',12,true}}},
+            _ = roundtrip('GeneralName', VallastName2),
+            ok
+    end.
 
 roundtrip(T, V) ->
     asn1_test_lib:roundtrip_enc('INSTANCEOF', T, V).
diff --git a/lib/asn1/test/testImporting.erl b/lib/asn1/test/testImporting.erl
index 79ad48c0f4..af44dfc5ad 100644
--- a/lib/asn1/test/testImporting.erl
+++ b/lib/asn1/test/testImporting.erl
@@ -20,15 +20,20 @@
 %%
 
 -module(testImporting).
--export([main/0]).
+-export([main/1]).
 
-main() ->
+main(Rule) ->
     M = 'Importing',
     roundtrip('Seq', {'Seq',5}),
     roundtrip('OtherSeq', {'Seq',42,true}),
     {'Seq',42,true} = M:seq(),
     roundtrip('ObjSeq', {'ObjSeq',1,<<"XYZ">>}),
-    roundtrip('ObjSeq', {'ObjSeq',2,19}),
+    case Rule of
+        jer ->
+            roundtrip('ObjSeq', {'ObjSeq',2,<<"19">>});
+        _ ->
+            roundtrip('ObjSeq', {'ObjSeq',2,19})
+    end,
     ok.
 
 roundtrip(Type, Value) ->
diff --git a/lib/asn1/test/testInfObj.erl b/lib/asn1/test/testInfObj.erl
index d3ec35b652..56b89bc7a1 100644
--- a/lib/asn1/test/testInfObj.erl
+++ b/lib/asn1/test/testInfObj.erl
@@ -27,150 +27,165 @@
 -record('InitiatingMessage2',{procedureCode,criticality,value}).
 -record('Iu-ReleaseCommand',{first,second}).
 
-main(_Erule) ->
+main(Erule) ->
+    OpenVal = case Erule of
+               jer ->
+                   {ok,Enc} = 
+                       'RANAPextract1':encode('Iu-ReleaseCommand',
+                                              #'Iu-ReleaseCommand'{
+                                                 first=13,
+                                                 second=true}),
+                   Enc;
+               _ ->
+                   #'Iu-ReleaseCommand'{
+                      first=13,
+                      second=true}
+           end,
     Val1 = #'InitiatingMessage'{procedureCode=1,
 				criticality=ignore,
-				value=#'Iu-ReleaseCommand'{
-				  first=13,
-				  second=true}},
+				value=OpenVal},
     roundtrip('RANAPextract1', 'InitiatingMessage', Val1),
     roundtrip('InfObj', 'InitiatingMessage', Val1),
 
-    Val2 = Val1#'InitiatingMessage'{procedureCode=2},
-    {error,_R1} = 'InfObj':encode('InitiatingMessage', Val2),
-    
-
-    %% Test case for OTP-4275
-    Val3 = #'InitiatingMessage2'{procedureCode=3,
-				 criticality=reject,
-				 value=#'Iu-ReleaseCommand'{
-				   first=13,
-				   second=true}},
-
-    roundtrip('RANAPextract1', 'InitiatingMessage2', Val3),
-
-    roundtrip('InfObj', 'MyPdu', {'MyPdu',42,12,false,"string"}),
-    roundtrip('InfObj', 'MyPdu', {'MyPdu',{'Seq',1023,<<"hello">>},
-				  42,true,"longer string"}),
-    roundtrip('InfObj', 'MyPdu', {'MyPdu',"75712346",43,true,"string"}),
-
-    roundtrip('InfObj', 'ConstructedPdu',
-	      {'ConstructedPdu',1,{'CONSTRUCTED-DEFAULT_Type',-2001,true}}),
-    roundtrip('InfObj', 'ConstructedPdu',
-	      {'ConstructedPdu',2,{'CONSTRUCTED-DEFAULT_Type',999,false}}),
-    roundtrip('InfObj', 'ConstructedPdu',
-	      {'ConstructedPdu',3,true}),
-    {'ConstructedPdu',4,{_,42,<<13:7>>}} =
-	enc_dec('InfObj', 'ConstructedPdu',
-		{'ConstructedPdu',4,{'',42,<<13:7>>}}),
-    roundtrip('InfObj', 'ConstructedPdu',
-	      {'ConstructedPdu',5,{i,-250138}}),
-    roundtrip('InfObj', 'ConstructedPdu',
-	      {'ConstructedPdu',5,{b,<<13456:15>>}}),
-    roundtrip('InfObj', 'ConstructedPdu',
-	      {'ConstructedPdu',6,[]}),
-    roundtrip('InfObj', 'ConstructedPdu',
-	      {'ConstructedPdu',6,[10,7,16,1,5,13,12]}),
-    roundtrip('InfObj', 'ConstructedPdu',
-	      {'ConstructedPdu',7,[]}),
-    roundtrip('InfObj', 'ConstructedPdu',
-	      {'ConstructedPdu',7,[64,1,19,17,35]}),
-    {'ConstructedPdu',8,[{_,-15,35},{_,533,-70}]} =
-	enc_dec('InfObj', 'ConstructedPdu',
-		{'ConstructedPdu',8,[{'_',-15,35},{'_',533,-70}]}),
-    {'ConstructedPdu',9,[{RecTag9,-15,35},{RecTag9,533,-70}]} =
-	enc_dec('InfObj', 'ConstructedPdu',
-		{'ConstructedPdu',9,[{'_',-15,35},{'_',533,-70}]}),
-
-    roundtrip('InfObj', 'ConstructedSet',
-	      {'ConstructedSet',1,{'CONSTRUCTED-DEFAULT_Type',-2001,true}}),
-    roundtrip('InfObj', 'ConstructedSet',
-	      {'ConstructedSet',2,{'CONSTRUCTED-DEFAULT_Type',999,false}}),
-    roundtrip('InfObj', 'ConstructedSet',
-	      {'ConstructedSet',3,true}),
-    {'ConstructedSet',4,{_,42,<<13:7>>}} =
-	enc_dec('InfObj', 'ConstructedSet',
-		{'ConstructedSet',4,{'',42,<<13:7>>}}),
-    roundtrip('InfObj', 'ConstructedSet',
-	      {'ConstructedSet',5,{i,-250138}}),
-    roundtrip('InfObj', 'ConstructedSet',
-	      {'ConstructedSet',5,{b,<<13456:15>>}}),
-    roundtrip('InfObj', 'ConstructedSet',
-	      {'ConstructedSet',6,[]}),
-    roundtrip('InfObj', 'ConstructedSet',
-	      {'ConstructedSet',6,[10,7,16,1,5,13,12]}),
-    roundtrip('InfObj', 'ConstructedSet',
-	      {'ConstructedSet',7,[]}),
-    roundtrip('InfObj', 'ConstructedSet',
-	      {'ConstructedSet',7,[64,1,19,17,35]}),
-    {'ConstructedSet',8,[{_,-15,35},{_,533,-70}]} =
-	enc_dec('InfObj', 'ConstructedSet',
-		{'ConstructedSet',8,[{'_',-15,35},{'_',533,-70}]}),
-    {'ConstructedSet',9,[{_,-15,35},{_,533,-70}]} =
-	enc_dec('InfObj', 'ConstructedSet',
-		{'ConstructedSet',9,[{'_',-15,35},{'_',533,-70}]}),
-
-    roundtrip('InfObj', 'Seq2',
-	      {'Seq2',42,[true,false,false,true],
-	       [false,true,false]}),
-
-    roundtrip('InfObj', 'OptionalInSeq', {'OptionalInSeq',3,true}),
-    roundtrip('InfObj', 'OptionalInSeq', {'OptionalInSeq',3,asn1_NOVALUE}),
-
-    roundtrip('InfObj', 'DefaultInSeq', {'DefaultInSeq',3,false}),
-    roundtrip('InfObj', 'DefaultInSeq', {'DefaultInSeq',3,true}),
-    {'DefaultInSeq',3,true} =
-	enc_dec('InfObj', 'DefaultInSeq', {'DefaultInSeq',3,asn1_DEFAULT}),
-
-    roundtrip('InfObj', 'Multiple-Optionals',
-	      {'Multiple-Optionals',1,42,true,<<"abc">>}),
-    roundtrip('InfObj', 'Multiple-Optionals',
-	      {'Multiple-Optionals',1,asn1_NOVALUE,true,<<"abc">>}),
-    roundtrip('InfObj', 'Multiple-Optionals',
-	      {'Multiple-Optionals',1,42,asn1_NOVALUE,<<"abc">>}),
-    roundtrip('InfObj', 'Multiple-Optionals',
-	      {'Multiple-Optionals',1,42,true,asn1_NOVALUE}),
-    roundtrip('InfObj', 'Multiple-Optionals',
-	      {'Multiple-Optionals',1,asn1_NOVALUE,asn1_NOVALUE,asn1_NOVALUE}),
-
-    test_objset('OstSeq12', [1,2]),
-    test_objset('OstSeq123', [1,2,3]),
-    test_objset('OstSeq1234', [1,2,3,4]),
-    test_objset('OstSeq45', [4,5]),
-    test_objset('OstSeq12345', [1,2,3,4,5]),
-
-    test_objset('OstSeq12Except', [1,2]),
-    test_objset('OstSeq123Except', [1,2]),
-
-    test_objset('ExOstSeq12', [1,2]),
-    test_objset('ExOstSeq123', [1,2,3]),
-    test_objset('ExOstSeq1234', [1,2,3,4]),
-    test_objset('ExOstSeq45', [4,5]),
-    test_objset('ExOstSeq12345', [1,2,3,4,5]),
-
-    test_objset('ExOstSeq12Except', [1,2]),
-    test_objset('ExOstSeq123Except', [1,2]),
-
-    roundtrip('InfObj', 'ExtClassSeq', {'ExtClassSeq', 4}),
-
-    {1,2,42} = 'InfObj':'value-1'(),
-    {1,2,42,25} = 'InfObj':'value-2'(),
-    {100,101} = 'InfObj':'value-3'(),
-    {1,2,100,101} = 'InfObj':'value-4'(),
-
-    roundtrip('InfObj', 'Rdn', {'Rdn',{2,5,4,41},"abc"}),
-
-    roundtrip('InfObj', 'TiAliasSeq',
-	      {'TiAliasSeq',{'TiAliasSeq_prf',{2,1,2},'NULL'}}),
-
-    roundtrip('InfObj', 'ContentInfo',
-	      {'ContentInfo',{2,7,8,9},"string"}),
-    {2,7,8,9} = 'InfObj':'id-content-type'(),
-
-    <<2#1011:4>> = 'InfObj':'tricky-bit-string'(),
-    <<16#CAFE:16>> = 'InfObj':'tricky-octet-string'(),
-
-    ok.
+    case Erule of
+        jer -> ok;
+        _ ->
+            Val2 = Val1#'InitiatingMessage'{procedureCode=2},
+            {error,_R1} = 'InfObj':encode('InitiatingMessage', Val2),
+            
+            
+            %% Test case for OTP-4275
+            Val3 = #'InitiatingMessage2'{procedureCode=3,
+                                         criticality=reject,
+                                         value=#'Iu-ReleaseCommand'{
+                                                  first=13,
+                                                  second=true}},
+            
+            roundtrip('RANAPextract1', 'InitiatingMessage2', Val3),
+            
+            roundtrip('InfObj', 'MyPdu', {'MyPdu',42,12,false,"string"}),
+            roundtrip('InfObj', 'MyPdu', {'MyPdu',{'Seq',1023,<<"hello">>},
+                                          42,true,"longer string"}),
+            roundtrip('InfObj', 'MyPdu', {'MyPdu',"75712346",43,true,"string"}),
+            
+            roundtrip('InfObj', 'ConstructedPdu',
+                      {'ConstructedPdu',1,{'CONSTRUCTED-DEFAULT_Type',-2001,true}}),
+            roundtrip('InfObj', 'ConstructedPdu',
+                      {'ConstructedPdu',2,{'CONSTRUCTED-DEFAULT_Type',999,false}}),
+            roundtrip('InfObj', 'ConstructedPdu',
+                      {'ConstructedPdu',3,true}),
+            {'ConstructedPdu',4,{_,42,<<13:7>>}} =
+                enc_dec('InfObj', 'ConstructedPdu',
+                        {'ConstructedPdu',4,{'',42,<<13:7>>}}),
+            roundtrip('InfObj', 'ConstructedPdu',
+                      {'ConstructedPdu',5,{i,-250138}}),
+            roundtrip('InfObj', 'ConstructedPdu',
+                      {'ConstructedPdu',5,{b,<<13456:15>>}}),
+            roundtrip('InfObj', 'ConstructedPdu',
+                      {'ConstructedPdu',6,[]}),
+            roundtrip('InfObj', 'ConstructedPdu',
+                      {'ConstructedPdu',6,[10,7,16,1,5,13,12]}),
+            roundtrip('InfObj', 'ConstructedPdu',
+                      {'ConstructedPdu',7,[]}),
+            roundtrip('InfObj', 'ConstructedPdu',
+                      {'ConstructedPdu',7,[64,1,19,17,35]}),
+            {'ConstructedPdu',8,[{_,-15,35},{_,533,-70}]} =
+                enc_dec('InfObj', 'ConstructedPdu',
+                        {'ConstructedPdu',8,[{'_',-15,35},{'_',533,-70}]}),
+            {'ConstructedPdu',9,[{RecTag9,-15,35},{RecTag9,533,-70}]} =
+                enc_dec('InfObj', 'ConstructedPdu',
+                        {'ConstructedPdu',9,[{'_',-15,35},{'_',533,-70}]}),
+            
+            roundtrip('InfObj', 'ConstructedSet',
+                      {'ConstructedSet',1,{'CONSTRUCTED-DEFAULT_Type',-2001,true}}),
+            roundtrip('InfObj', 'ConstructedSet',
+                      {'ConstructedSet',2,{'CONSTRUCTED-DEFAULT_Type',999,false}}),
+            roundtrip('InfObj', 'ConstructedSet',
+                      {'ConstructedSet',3,true}),
+            {'ConstructedSet',4,{_,42,<<13:7>>}} =
+                enc_dec('InfObj', 'ConstructedSet',
+                        {'ConstructedSet',4,{'',42,<<13:7>>}}),
+            roundtrip('InfObj', 'ConstructedSet',
+                      {'ConstructedSet',5,{i,-250138}}),
+            roundtrip('InfObj', 'ConstructedSet',
+                      {'ConstructedSet',5,{b,<<13456:15>>}}),
+            roundtrip('InfObj', 'ConstructedSet',
+                      {'ConstructedSet',6,[]}),
+            roundtrip('InfObj', 'ConstructedSet',
+                      {'ConstructedSet',6,[10,7,16,1,5,13,12]}),
+            roundtrip('InfObj', 'ConstructedSet',
+                      {'ConstructedSet',7,[]}),
+            roundtrip('InfObj', 'ConstructedSet',
+                      {'ConstructedSet',7,[64,1,19,17,35]}),
+            {'ConstructedSet',8,[{_,-15,35},{_,533,-70}]} =
+                enc_dec('InfObj', 'ConstructedSet',
+                        {'ConstructedSet',8,[{'_',-15,35},{'_',533,-70}]}),
+            {'ConstructedSet',9,[{_,-15,35},{_,533,-70}]} =
+                enc_dec('InfObj', 'ConstructedSet',
+                        {'ConstructedSet',9,[{'_',-15,35},{'_',533,-70}]}),
+            
+            roundtrip('InfObj', 'Seq2',
+                      {'Seq2',42,[true,false,false,true],
+                       [false,true,false]}),
+            
+            roundtrip('InfObj', 'OptionalInSeq', {'OptionalInSeq',3,true}),
+            roundtrip('InfObj', 'OptionalInSeq', {'OptionalInSeq',3,asn1_NOVALUE}),
+            
+            roundtrip('InfObj', 'DefaultInSeq', {'DefaultInSeq',3,false}),
+            roundtrip('InfObj', 'DefaultInSeq', {'DefaultInSeq',3,true}),
+            {'DefaultInSeq',3,true} =
+                enc_dec('InfObj', 'DefaultInSeq', {'DefaultInSeq',3,asn1_DEFAULT}),
+            
+            roundtrip('InfObj', 'Multiple-Optionals',
+                      {'Multiple-Optionals',1,42,true,<<"abc">>}),
+            roundtrip('InfObj', 'Multiple-Optionals',
+                      {'Multiple-Optionals',1,asn1_NOVALUE,true,<<"abc">>}),
+            roundtrip('InfObj', 'Multiple-Optionals',
+                      {'Multiple-Optionals',1,42,asn1_NOVALUE,<<"abc">>}),
+            roundtrip('InfObj', 'Multiple-Optionals',
+                      {'Multiple-Optionals',1,42,true,asn1_NOVALUE}),
+            roundtrip('InfObj', 'Multiple-Optionals',
+                      {'Multiple-Optionals',1,asn1_NOVALUE,asn1_NOVALUE,asn1_NOVALUE}),
+            
+            test_objset('OstSeq12', [1,2]),
+            test_objset('OstSeq123', [1,2,3]),
+            test_objset('OstSeq1234', [1,2,3,4]),
+            test_objset('OstSeq45', [4,5]),
+            test_objset('OstSeq12345', [1,2,3,4,5]),
+            
+            test_objset('OstSeq12Except', [1,2]),
+            test_objset('OstSeq123Except', [1,2]),
+            
+            test_objset('ExOstSeq12', [1,2]),
+            test_objset('ExOstSeq123', [1,2,3]),
+            test_objset('ExOstSeq1234', [1,2,3,4]),
+            test_objset('ExOstSeq45', [4,5]),
+            test_objset('ExOstSeq12345', [1,2,3,4,5]),
+            
+            test_objset('ExOstSeq12Except', [1,2]),
+            test_objset('ExOstSeq123Except', [1,2]),
+            
+            roundtrip('InfObj', 'ExtClassSeq', {'ExtClassSeq', 4}),
+            
+            {1,2,42} = 'InfObj':'value-1'(),
+            {1,2,42,25} = 'InfObj':'value-2'(),
+            {100,101} = 'InfObj':'value-3'(),
+            {1,2,100,101} = 'InfObj':'value-4'(),
+            
+            roundtrip('InfObj', 'Rdn', {'Rdn',{2,5,4,41},"abc"}),
+            
+            roundtrip('InfObj', 'TiAliasSeq',
+                      {'TiAliasSeq',{'TiAliasSeq_prf',{2,1,2},'NULL'}}),
+            
+            roundtrip('InfObj', 'ContentInfo',
+                      {'ContentInfo',{2,7,8,9},"string"}),
+            {2,7,8,9} = 'InfObj':'id-content-type'(),
+            
+            <<2#1011:4>> = 'InfObj':'tricky-bit-string'(),
+            <<16#CAFE:16>> = 'InfObj':'tricky-octet-string'(),
+            
+            ok
+    end.
 
 test_objset(Type, Keys) ->
     _ = [test_object(Type, Key) || Key <- Keys],
diff --git a/lib/asn1/test/testInfObjExtract.erl b/lib/asn1/test/testInfObjExtract.erl
index b51611f95f..f48a63df2f 100644
--- a/lib/asn1/test/testInfObjExtract.erl
+++ b/lib/asn1/test/testInfObjExtract.erl
@@ -21,9 +21,10 @@
 
 -module(testInfObjExtract).
 
--export([main/0]).
+-export([main/1]).
 
-main() ->
+main(jer) -> ok;
+main(_Rule) ->
     roundtrip_data_object_13('DataSeq-1'),
 
     roundtrip_data_object_1('DataSeq-2'),
diff --git a/lib/asn1/test/testInfObjectClass.erl b/lib/asn1/test/testInfObjectClass.erl
index 02ff38e78a..a6f54fd619 100644
--- a/lib/asn1/test/testInfObjectClass.erl
+++ b/lib/asn1/test/testInfObjectClass.erl
@@ -29,23 +29,32 @@
 main(Rule) ->
     %% this test is added for OTP-4591, to test that elements in decoded
     %% value has terms in right order.
-    Val = {'Seq',12,13,2},
+    Val = case Rule of
+              %% table constraints are not JER visible
+              %% The binaries here are Open Types which in this case
+              %% are JSON encodings of INTEGER
+              jer -> {'Seq',<<"12">>,<<"13">>,2}; 
+              _ -> {'Seq',12,13,2}
+          end,
     roundtrip('Seq', Val),
-    
-    %% OTP-5783
-    {'Type not compatible with table constraint',
-     {component,'ArgumentType'},
-     {value,_},_} = enc_error('Seq', {'Seq',12,13,1}),
-    Bytes2 = case Rule of
-		 ber ->
-		     <<48,9,2,1,12,2,1,11,2,1,1>>;
-		 _ ->
-		     <<1,12,1,11,1,1>>
-	     end,
-    {'Type not compatible with table constraint',
-     {{component,_},
-      {value,_B},_}} = dec_error('Seq', Bytes2),
-    ok.
+    case Rule of
+        jer -> ok; % table constraints are not JER visible
+        _ ->
+            %% OTP-5783
+            {'Type not compatible with table constraint',
+             {component,'ArgumentType'},
+             {value,_},_} = enc_error('Seq', {'Seq',12,13,1}),
+            Bytes2 = case Rule of
+                         ber ->
+                             <<48,9,2,1,12,2,1,11,2,1,1>>;
+                         _ ->
+                             <<1,12,1,11,1,1>>
+                     end,
+            {'Type not compatible with table constraint',
+             {{component,_},
+              {value,_B},_}} = dec_error('Seq', Bytes2),
+            ok
+    end.
 
 roundtrip(T, V) ->
     asn1_test_lib:roundtrip('InfClass', T, V).
diff --git a/lib/asn1/test/testMergeCompile.erl b/lib/asn1/test/testMergeCompile.erl
index f0e68e07b7..bc7fdc888f 100644
--- a/lib/asn1/test/testMergeCompile.erl
+++ b/lib/asn1/test/testMergeCompile.erl
@@ -28,6 +28,7 @@
 -record('InitiatingMessage',{procedureCode,criticality,value}).
 -record('Iu-ReleaseCommand',{protocolIEs,protocolExtensions}).
 
+main(jer) -> ok;
 main(Erule) ->
     %% test of module MS.set.asn that tests OTP-4492: different tagdefault in 
     %% modules and types  with same name in modules
diff --git a/lib/asn1/test/testOpenTypeImplicitTag.erl b/lib/asn1/test/testOpenTypeImplicitTag.erl
index b1534bd268..f4b488ce19 100644
--- a/lib/asn1/test/testOpenTypeImplicitTag.erl
+++ b/lib/asn1/test/testOpenTypeImplicitTag.erl
@@ -24,10 +24,16 @@
 
 -include_lib("common_test/include/ct.hrl").
 
+
+main(jer) ->
+    roundtrip('Seq', {'Seq',<<"123">>,<<"456">>,12,<<"789">>}),
+    roundtrip('Seq', {'Seq',<<"4711">>,asn1_NOVALUE,12,<<"1137">>}),
+    ok;
 main(_Rules) ->
     roundtrip('Seq', {'Seq',<<1,1,255>>,<<1,1,255>>,12,<<1,1,255>>}),
     roundtrip('Seq', {'Seq',<<1,1,255>>,asn1_NOVALUE,12,<<1,1,255>>}),
     ok.
 
+
 roundtrip(T, V) ->
     asn1_test_lib:roundtrip('OpenTypeImplicitTag', T, V).
diff --git a/lib/asn1/test/testPrim.erl b/lib/asn1/test/testPrim.erl
index a5d34f5f08..3f687e754f 100644
--- a/lib/asn1/test/testPrim.erl
+++ b/lib/asn1/test/testPrim.erl
@@ -36,9 +36,10 @@ bool(Rules) ->
     [roundtrip(T, V) || T <- Types, V <- [true,false]],
     Tag = case Rules of
               ber -> encode_boolean;
+              jer -> {encode,'BOOLEAN'};
               _ -> illegal_boolean
           end,
-    [{Tag,517} = enc_error(T, 517) || T <- Types],
+    [{ok,517} = enc_error(Tag,T, 517) || T <- Types],
     ok.
 
 
@@ -62,15 +63,16 @@ int(Rules) ->
     _ = [roundtrip(T, V) || T <- Types, V <- [1|Values]],
     Tag = case Rules of
               ber -> encode_integer;
+              jer -> '_';
               _ -> illegal_integer
           end,
-    _ = [{Tag,V} = enc_error(T, V) ||
+    _ = [{ok,V} = enc_error(Tag,T, V) ||
             T <- Types, V <- [atom,42.0,{a,b,c}]],
     case Rules of
         ber ->
             ok;
         _ ->
-            _ = [{Tag,V} = enc_error('IntConstrained', V) ||
+            _ = [{ok,V} = enc_error(Tag,'IntConstrained', V) ||
                     V <- [atom,-1,256,42.0]]
     end,
 
@@ -108,8 +110,10 @@ int(Rules) ->
 
     ok.
 
-encoding(Rules, Type) ->
-    asn1_test_lib:hex_to_bin(encoding_1(Rules, Type)).
+encoding(jer,oneMicrodegreeEast) -> <<"10">>;
+encoding(jer,oneMicrodegreeWest) -> <<"-10">>;
+encoding(Rule, Val) ->
+    asn1_test_lib:hex_to_bin(encoding_1(Rule, Val)).
 
 encoding_1(ber, oneMicrodegreeEast) -> "02010A";
 encoding_1(per, oneMicrodegreeEast) -> "C06B49D2 09";
@@ -130,16 +134,19 @@ enum(Rules) ->
     roundtrip('Enum', thursday),
     Tag = case Rules of
               ber -> enumerated_not_in_range;
+              jer -> '_';
               _ -> illegal_enumerated
           end,
-    {Tag,4} = enc_error('Enum', 4),
+    {ok,4} = enc_error(Tag,'Enum', 4),
 
     case Rules of
 	Per when Per =:= per; Per =:= uper ->
 	    <<0>> = roundtrip('SingleEnumVal', true),
 	    <<0>> = roundtrip('SingleEnumValExt', true);
 	ber ->
-	    ok
+	    ok;
+        jer ->
+            ok
     end,
 
     roundtrip('NegEnumVal', neg),
@@ -192,22 +199,29 @@ roundtrip(Type, Value, ExpectedValue) ->
 	    Enc
     end.
 
-enc_error(T, V) ->
-    case get(no_ok_wrapper) of
-	false ->
-	    {error,{asn1,{Reason,Stk}}} = 'Prim':encode(T, V),
-            [{_,_,_,_}|_] = Stk,
-            Reason;
-	true ->
-	    try 'Prim':encode(T, V) of
-		_ ->
-		    ?t:fail()
-	    catch
-		_:{error,{asn1,Reason}} ->
-		    Reason
-	    end
+enc_error(Tag,T, V) ->
+    {Rtag,Val} = case get(no_ok_wrapper) of
+                     false ->
+                         {error,{asn1,{Reason,Stk}}} = 'Prim':encode(T, V),
+                         [{_,_,_,_}|_] = Stk,
+                         Reason;
+                     true ->
+                         try 'Prim':encode(T, V) of
+                             _ ->
+                                 ?t:fail()
+                         catch
+                             _:{error,{asn1,Reason}} ->
+                                 Reason
+                         end
+                 end,
+    case Tag of
+        '_' -> % Any tag is accepted 
+            {ok,Val};
+        Rtag -> % A specific tag given as first argument is accepted
+            {ok,Val}
     end.
 
+real(jer) -> ok; % Temporary workaround
 real(_Rules) ->
     %%==========================================================
     %% AngleInRadians ::= REAL
diff --git a/lib/asn1/test/testTCAP.erl b/lib/asn1/test/testTCAP.erl
index d892863f5e..f34499be9c 100644
--- a/lib/asn1/test/testTCAP.erl
+++ b/lib/asn1/test/testTCAP.erl
@@ -38,6 +38,7 @@ compile_asn1config(Config, Options) ->
     asn1_test_lib:compile_all(Files, Config, Options),
     asn1_test_lib:compile_erlang("TCAPPackage_msg", Config, []).
 
+test(jer,_) -> ok;
 test(Erule,_Config) ->
     %% testing OTP-4798, open type encoded with indefinite length
     {ok,_Res} = 'TCAPMessages-simple':decode('MessageType',
diff --git a/lib/asn1/test/testUniqueObjectSets.erl b/lib/asn1/test/testUniqueObjectSets.erl
index 0c61da96a1..963e1863f6 100644
--- a/lib/asn1/test/testUniqueObjectSets.erl
+++ b/lib/asn1/test/testUniqueObjectSets.erl
@@ -49,6 +49,7 @@ types() ->
      {"SET OF SEQUENCE {x INTEGER (0..7)}",[{'_',7},{'_',0}]}
     ].
 
+main(_,jer,_) -> ok;
 main(CaseDir, Rule, Opts) ->
     D0 = types(),
     {D1,_} = lists:mapfoldl(fun({T,S}, I) ->
-- 
2.16.4

openSUSE Build Service is sponsored by