File 2414-Teach-the-ASN.1-compiler-the-maps-option.patch of Package erlang

From 8a7f914affce3102e4889c2973ea2d2e99ad633d Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Mon, 16 Jan 2017 16:47:58 +0100
Subject: [PATCH 14/14] Teach the ASN.1 compiler the 'maps' option

When the 'maps' option is given, the SEQUENCE and SET types are
represented as maps instead of as records. Optional and default values
must be not be given as asn1_NOVALUE or asn1_DEFAULT in a map passed
to the M:encode/2 function; they must be omitted from the
map. Similarly, when decoding missing values will be omitted from the
map.

No .hrl files will be generated when the 'maps' options is used.
That means values in an ASN.1 module must be retrieved by calling the
appropriate function in generated module.

Since we one day hope to get rid of the options 'compact_bit_string',
'legacy_bit_string', and 'legacy_erlang_types', we will not allow them
to be combined with the 'maps' option.
---
 lib/asn1/doc/src/asn1_getting_started.xml      |  77 +++-
 lib/asn1/doc/src/asn1ct.xml                    |  17 +-
 lib/asn1/src/asn1_db.erl                       |  26 +-
 lib/asn1/src/asn1_records.hrl                  |   2 +
 lib/asn1/src/asn1ct.erl                        |  43 +-
 lib/asn1/src/asn1ct_check.erl                  |  26 +-
 lib/asn1/src/asn1ct_constructed_ber_bin_v2.erl | 273 ++++++++-----
 lib/asn1/src/asn1ct_constructed_per.erl        | 544 +++++++++++++++++--------
 lib/asn1/src/asn1ct_eval_ext.funcs             |   1 +
 lib/asn1/src/asn1ct_gen.erl                    |  18 +-
 lib/asn1/src/asn1ct_gen_ber_bin_v2.erl         |  12 +-
 lib/asn1/src/asn1ct_gen_check.erl              | 191 ++++++---
 lib/asn1/src/asn1ct_imm.erl                    |  41 +-
 lib/asn1/src/asn1ct_value.erl                  |  24 +-
 lib/asn1/src/asn1rtt_ext.erl                   |  62 ++-
 lib/asn1/test/Makefile                         |   1 +
 lib/asn1/test/asn1_SUITE.erl                   |  76 +++-
 lib/asn1/test/asn1_SUITE_data/Maps.asn1        |  17 +
 lib/asn1/test/asn1_test_lib.erl                | 105 ++++-
 lib/asn1/test/testContextSwitchingTypes.erl    |   1 +
 lib/asn1/test/testInfObj.erl                   |   1 +
 lib/asn1/test/testMaps.erl                     |  50 +++
 lib/asn1/test/testRfcs.erl                     |  50 ++-
 lib/asn1/test/testTCAP.erl                     |   1 +
 lib/asn1/test/testTimer.erl                    | 131 ++++--
 lib/asn1/test/testUniqueObjectSets.erl         |   1 +
 lib/asn1/test/test_compile_options.erl         |  28 +-
 27 files changed, 1349 insertions(+), 470 deletions(-)
 create mode 100644 lib/asn1/test/asn1_SUITE_data/Maps.asn1
 create mode 100644 lib/asn1/test/testMaps.erl

diff --git a/lib/asn1/doc/src/asn1_getting_started.xml b/lib/asn1/doc/src/asn1_getting_started.xml
index d40b294c3..d2b73d63c 100644
--- a/lib/asn1/doc/src/asn1_getting_started.xml
+++ b/lib/asn1/doc/src/asn1_getting_started.xml
@@ -187,6 +187,14 @@ erlc -o ../asnfiles -I ../asnfiles -I /usr/local/standards/asn1 Person.asn</pre>
         <item>
           <p>DER encoding rule. Only when using option <c>-ber</c>.</p>
         </item>
+        <tag><c>+maps</c></tag>
+        <item>
+          <p>Use maps instead of records to represent the <c>SEQUENCE</c> and
+	  <c>SET</c> types. No <c>.hrl</c> files will be generated.
+	  See the Section <seealso marker="asn1_getting_started#MAP_SEQ_SET">
+	  Map representation for SEQUENCE and SET</seealso>
+	  for more information.</p>
+        </item>
         <tag><c>+asn1config</c></tag>
         <item>
           <p>This functionality works together with option
@@ -766,8 +774,11 @@ Pdu ::= SEQUENCE {
    b REAL,
    c OBJECT IDENTIFIER,
    d NULL }      </pre>
-      <p>This is a 4-component structure called <c>Pdu</c>. The record format
-        is the major format for representation of <c>SEQUENCE</c> in Erlang.
+      <p>This is a 4-component structure called <c>Pdu</c>. By default,
+        a <c>SEQUENCE</c> is represented by a record in Erlang.
+	It can also be represented as a map; see
+	<seealso marker="asn1_getting_started#MAP_SEQ_SET">
+	Map representation for SEQUENCE and SET</seealso>.
         For each <c>SEQUENCE</c> and <c>SET</c> in an ASN.1 module an Erlang
         record declaration is generated. For <c>Pdu</c>, a record
         like the following is defined:</p>
@@ -878,6 +889,48 @@ SExt ::= SEQUENCE {
     </section>
 
     <section>
+      <marker id="MAP_SEQ_SET"></marker>
+      <title>Map representation for SEQUENCE and SET</title>
+      <p>If the ASN.1 module has been compiled with option <c>maps</c>,
+      the types <c>SEQUENCE</c> and <c>SET</c> are represented as maps.</p>
+      <p>In the following example, this ASN.1 specification is used:</p>
+      <pre>
+File DEFINITIONS AUTOMATIC TAGS ::=
+BEGIN
+Seq1 ::= SEQUENCE {
+    a INTEGER DEFAULT 42,
+    b BOOLEAN OPTIONAL,
+    c IA5String
+}
+END   </pre>
+
+      <p>Optional fields are to be omitted from the map if they have
+      no value:</p>
+
+      <pre>
+1> <input>asn1ct:compile('File', [per,maps]).</input>
+ok
+2> <input>{ok,E} = 'File':encode('Seq1', #{a=>0,c=>"string"}).</input>
+{ok,&lt;&lt;128,1,0,6,115,116,114,105,110,103&gt;&gt;} </pre>
+
+      <p>When decoding, optional fields will be omitted from the map:</p>
+
+      <pre>
+3> <input>'File':decode('Seq1', E).</input>
+{ok,#{a => 0,c => "string"}}   </pre>
+
+      <p>Default values can be omitted from the map:</p>
+      <pre>
+4> <input>{ok,E2} = 'File':encode('Seq1', #{c=>"string"}).</input>
+{ok,&lt;&lt;0,6,115,116,114,105,110,103&gt;&gt;}
+5> <input>'File':decode('Seq1', E2).</input>
+{ok,#{a => 42,c => "string"}}   </pre>
+
+    <note><p>It is not allowed to use the atoms <c>asn1_VALUE</c> and
+    <c>asn1_DEFAULT</c> with maps.</p></note>
+    </section>
+
+    <section>
       <marker id="CHOICE"></marker>
       <title>CHOICE</title>
       <p>The type <c>CHOICE</c> is a space saver and is similar to the
@@ -1004,11 +1057,16 @@ T ::= CHOICE {
 
   <section>
     <title>Naming of Records in .hrl Files</title>
+    <p>When the option <c>maps</c> is given, no <c>.hrl</c> files
+    will be generated. The rest of this section describes the behavior
+    of the compiler when <c>maps</c> is not used.</p>
+
     <p>When an ASN.1 specification is compiled, all defined types of type
-      <c>SET</c> or <c>SEQUENCE</c> result in a corresponding record in the
-      generated <c>.hrl</c> file. This is because the values for
-      <c>SET</c> and <c>SEQUENCE</c> are represented as records as
-      mentioned earlier.</p>
+    <c>SET</c> or <c>SEQUENCE</c> result in a corresponding record in the
+    generated <c>.hrl</c> file. This is because the values for
+    <c>SET</c> and <c>SEQUENCE</c> are represented as records
+    by default.</p>
+
     <p>Some special cases of this functionality are presented in the
       next section.</p>
 
@@ -1144,9 +1202,10 @@ SS ::= SET {
     <p>This example shows that a function is generated by the compiler
       that returns a valid Erlang representation of the value, although
       the value is of a complex type.</p>
-    <p>Furthermore, a macro is generated for each value in the <c>.hrl</c>
-      file. So, the defined value <c>tt</c> can also be extracted by
-      <c>?tt</c> in application code.</p>
+    <p>Furthermore, if the option <c>maps</c> is not used,
+    a macro is generated for each value in the <c>.hrl</c>
+    file. So, the defined value <c>tt</c> can also be extracted by
+    <c>?tt</c> in application code.</p>
   </section>
 
   <section>
diff --git a/lib/asn1/doc/src/asn1ct.xml b/lib/asn1/doc/src/asn1ct.xml
index ebe1ce44d..859d6a50b 100644
--- a/lib/asn1/doc/src/asn1ct.xml
+++ b/lib/asn1/doc/src/asn1ct.xml
@@ -170,11 +170,24 @@ File3.asn</pre>
               as for <c>ber</c>.
 	    </p>
           </item>
+          <tag><c>maps</c></tag>
+          <item>
+	    <p>This option changes the representation of the types
+	    <c>SEQUENCE</c> and <c>SET</c> to use maps (instead of
+	    records).  This option also suppresses the generation of
+	    <c>.hrl</c> files.</p>
+	    <p>For details, see Section
+	      <seealso marker="asn1_getting_started#MAP_SEQ_SET">
+		Map representation for SEQUENCE and SET</seealso>
+		in the User's Guide.
+	    </p>
+	  </item>
           <tag><c>compact_bit_string</c></tag>
           <item>
             <p>
 	      The <c>BIT STRING</c> type is decoded to "compact notation".
 	      <em>This option is not recommended for new code.</em>
+	      This option cannot be combined with the option <c>maps</c>.
 	    </p>
 	    <p>For details, see Section
 	      <seealso marker="asn1_getting_started#BIT STRING">
@@ -188,6 +201,7 @@ File3.asn</pre>
 	      The <c>BIT STRING</c> type is decoded to the legacy
 	      format, that is, a list of zeroes and ones.
 	      <em>This option is not recommended for new code.</em>
+	      This option cannot be combined with the option <c>maps</c>.
 	    </p>
 	    <p>For details, see Section
 	      <seealso marker="asn1_getting_started#BIT STRING">BIT STRING</seealso>
@@ -202,7 +216,8 @@ File3.asn</pre>
             marker="asn1_getting_started#BIT STRING">BIT STRING</seealso> and Section
             <seealso marker="asn1_getting_started#OCTET STRING">OCTET
             STRING</seealso> in the User's Guide.</p>
-	    <p><em>This option is not recommended for new code.</em></p>
+	    <p><em>This option is not recommended for new code.</em>
+	    This option cannot be combined with the option <c>maps</c>.</p>
 	  </item>
           <tag><c>{n2n, EnumTypeName}</c></tag>
           <item>
diff --git a/lib/asn1/src/asn1_db.erl b/lib/asn1/src/asn1_db.erl
index 869ea310a..a3e45ca91 100644
--- a/lib/asn1/src/asn1_db.erl
+++ b/lib/asn1/src/asn1_db.erl
@@ -20,7 +20,7 @@
 %%
 -module(asn1_db).
 
--export([dbstart/1,dbnew/2,dbload/1,dbload/3,dbsave/2,dbput/2,
+-export([dbstart/1,dbnew/3,dbload/1,dbload/4,dbsave/2,dbput/2,
 	 dbput/3,dbget/2]).
 -export([dbstop/0]).
 
@@ -37,13 +37,13 @@ dbstart(Includes0) ->
     put(?MODULE, spawn_link(fun() -> init(Parent, Includes) end)),
     ok.
 
-dbload(Module, Erule, Mtime) ->
-    req({load, Module, Erule, Mtime}).
+dbload(Module, Erule, Maps, Mtime) ->
+    req({load, Module, {Erule,Maps}, Mtime}).
 
 dbload(Module) ->
     req({load, Module, any, {{0,0,0},{0,0,0}}}).
 
-dbnew(Module, Erule)       -> req({new, Module, Erule}).
+dbnew(Module, Erule, Maps) -> req({new, Module, {Erule,Maps}}).
 dbsave(OutFile, Module)    -> cast({save, OutFile, Module}).
 dbput(Module, K, V)        -> cast({set, Module, K, V}).
 dbput(Module, Kvs)         -> cast({set, Module, Kvs}).
@@ -110,19 +110,19 @@ loop(#state{parent = Parent, monitor = MRef, table = Table,
             ok = ets:tab2file(Mtab, TempFile),
 	    ok = file:rename(TempFile, OutFile),
             loop(State);
-        {From, {new, Mod, Erule}} ->
+        {From, {new, Mod, EruleMaps}} ->
             [] = ets:lookup(Table, Mod),	%Assertion.
             ModTableId = ets:new(list_to_atom(lists:concat(["asn1_",Mod])), []),
             ets:insert(Table, {Mod, ModTableId}),
-	    ets:insert(ModTableId, {?MAGIC_KEY, info(Erule)}),
+	    ets:insert(ModTableId, {?MAGIC_KEY, info(EruleMaps)}),
             reply(From, ok),
             loop(State);
-	{From, {load, Mod, Erule, Mtime}} ->
+	{From, {load, Mod, EruleMaps, Mtime}} ->
 	    case ets:member(Table, Mod) of
 		true ->
 		    reply(From, ok);
 		false ->
-		    case load_table(Mod, Erule, Mtime, Includes) of
+		    case load_table(Mod, EruleMaps, Mtime, Includes) of
 			{ok, ModTableId} ->
 			    ets:insert(Table, {Mod, ModTableId}),
 			    reply(From, ok);
@@ -151,20 +151,20 @@ lookup(Tab, K) ->
         [{K,V}] -> V
     end.
 
-info(Erule) ->
-    {asn1ct:vsn(),Erule}.
+info(EruleMaps) ->
+    {asn1ct:vsn(),EruleMaps}.
 
-load_table(Mod, Erule, Mtime, Includes) ->
+load_table(Mod, EruleMaps, Mtime, Includes) ->
     Base = lists:concat([Mod, ".asn1db"]),
     case path_find(Includes, Mtime, Base) of
 	error ->
 	    error;
-	{ok,ModTab} when Erule =:= any ->
+	{ok,ModTab} when EruleMaps =:= any ->
 	    {ok,ModTab};
 	{ok,ModTab} ->
 	    Vsn = asn1ct:vsn(),
 	    case ets:lookup(ModTab, ?MAGIC_KEY) of
-		[{_,{Vsn,Erule}}] ->
+		[{_,{Vsn,EruleMaps}}] ->
 		    %% Correct version and encoding rule.
 		    {ok,ModTab};
 		_ ->
diff --git a/lib/asn1/src/asn1_records.hrl b/lib/asn1/src/asn1_records.hrl
index 4b800f17c..d3d76f956 100644
--- a/lib/asn1/src/asn1_records.hrl
+++ b/lib/asn1/src/asn1_records.hrl
@@ -28,6 +28,7 @@
 -define('COMPLETE_ENCODE',1).
 -define('TLV_DECODE',2).
 
+-define(MISSING_IN_MAP, asn1__MISSING_IN_MAP).
 
 -record(module,{pos,name,defid,tagdefault='EXPLICIT',exports={exports,[]},imports={imports,[]}, extensiondefault=empty,typeorval}).
 
@@ -103,6 +104,7 @@
          aligned=false :: boolean(),
          rec_prefix="" :: string(),
          macro_prefix="" :: string(),
+         pack=record :: 'record' | 'map',
          options=[] :: [any()]
         }).
 
diff --git a/lib/asn1/src/asn1ct.erl b/lib/asn1/src/asn1ct.erl
index 0a68395b4..d27f8897a 100644
--- a/lib/asn1/src/asn1ct.erl
+++ b/lib/asn1/src/asn1ct.erl
@@ -193,7 +193,7 @@ check_pass(#st{code=M,file=File,includes=Includes,
 	       erule=Erule,dbfile=DbFile,opts=Opts,
 	       inputmodules=InputModules}=St) ->
     start(Includes),
-    case asn1ct_check:storeindb(#state{erule=Erule}, M) of
+    case asn1ct_check:storeindb(#state{erule=Erule,options=Opts}, M) of
 	ok ->
 	    Module = asn1_db:dbget(M#module.name, 'MODULE'),
 	    State = #state{mname=Module#module.name,
@@ -216,8 +216,8 @@ check_pass(#st{code=M,file=File,includes=Includes,
 	    {error,St#st{error=Reason}}
     end.
 
-save_pass(#st{code=M,erule=Erule}=St) ->
-    ok = asn1ct_check:storeindb(#state{erule=Erule}, M),
+save_pass(#st{code=M,erule=Erule,opts=Opts}=St) ->
+    ok = asn1ct_check:storeindb(#state{erule=Erule,options=Opts}, M),
     {ok,St}.
 
 parse_listing(#st{code=Code,outfile=OutFile0}=St) ->
@@ -842,6 +842,8 @@ generate({M,GenTOrV}, OutFile, EncodingRule, Options) ->
 
     Gen = init_gen_record(EncodingRule, Options),
 
+    check_maps_option(Gen),
+
     %% create decoding function names and taglists for partial decode
     try
         specialized_decode_prepare(Gen, M)
@@ -875,9 +877,13 @@ init_gen_record(EncodingRule, Options) ->
     Aligned = EncodingRule =:= per,
     RecPrefix = proplists:get_value(record_name_prefix, Options, ""),
     MacroPrefix = proplists:get_value(macro_name_prefix, Options, ""),
+    Pack = case proplists:get_value(maps, Options, false) of
+               true -> map;
+               false -> record
+           end,
     #gen{erule=Erule,der=Der,aligned=Aligned,
          rec_prefix=RecPrefix,macro_prefix=MacroPrefix,
-         options=Options}.
+         pack=Pack,options=Options}.
 
 
 setup_legacy_erlang_types(Opts) ->
@@ -924,6 +930,26 @@ cleanup_bit_string_format() ->
 get_bit_string_format() ->
     get(bit_string_format).
 
+check_maps_option(#gen{pack=map}) ->
+    case get_bit_string_format() of
+        bitstring ->
+            ok;
+        _ ->
+            Message1 = "The 'maps' option must not be combined with "
+                "'compact_bit_string' or 'legacy_bit_string'",
+            exit({error,{asn1,Message1}})
+    end,
+    case use_legacy_types() of
+        false ->
+            ok;
+        true ->
+            Message2 = "The 'maps' option must not be combined with "
+                "'legacy_erlang_types'",
+            exit({error,{asn1,Message2}})
+    end;
+check_maps_option(#gen{}) ->
+    ok.
+
 
 %% parse_and_save parses an asn1 spec and saves the unchecked parse
 %% tree in a data base file.
@@ -933,22 +959,27 @@ parse_and_save(Module,S) ->
     SourceDir = S#state.sourcedir,
     Includes = [I || {i,I} <- Options],
     Erule = S#state.erule,
+    Maps = lists:member(maps, Options),
     case get_input_file(Module, [SourceDir|Includes]) of
 	%% search for asn1 source
 	{file,SuffixedASN1source} ->
 	    Mtime = filelib:last_modified(SuffixedASN1source),
-	    case asn1_db:dbload(Module, Erule, Mtime) of
+	    case asn1_db:dbload(Module, Erule, Maps, Mtime) of
 		ok -> ok;
 		error -> parse_and_save1(S, SuffixedASN1source, Options)
 	    end;
-	Err ->
+	Err when not Maps ->
 	    case asn1_db:dbload(Module) of
 		ok ->
+                    %% FIXME: This should be an error.
 		    warning("could not do a consistency check of the ~p file: no asn1 source file was found.~n",
 			    [lists:concat([Module,".asn1db"])],Options);
 		error ->
 		    ok
 	    end,
+	    {error,{asn1,input_file_error,Err}};
+        Err ->
+            %% Always fail directly when the 'maps' option is used.
 	    {error,{asn1,input_file_error,Err}}
     end.
 
diff --git a/lib/asn1/src/asn1ct_check.erl b/lib/asn1/src/asn1ct_check.erl
index a01a22ddc..321f4147f 100644
--- a/lib/asn1/src/asn1ct_check.erl
+++ b/lib/asn1/src/asn1ct_check.erl
@@ -2239,12 +2239,18 @@ normalized_record(SorS,S,Value,Components,NameList) ->
     case is_record_normalized(S,NewName,Value,length(Components)) of
 	true ->
 	    Value;
-	_ ->
+	false ->
 	    NoComps = length(Components),
 	    ListOfVals = normalize_seq_or_set(SorS,S,Value,Components,NameList,[]),
-	    NoComps = length(ListOfVals), %% Assert
-	    list_to_tuple([NewName|ListOfVals])
+	    NoComps = length(ListOfVals),       %Assertion.
+            case use_maps(S) of
+                false ->
+                    list_to_tuple([NewName|ListOfVals]);
+                true ->
+                    create_map_value(Components, ListOfVals)
+            end
     end.
+
 is_record_normalized(S,Name,V = #'Externalvaluereference'{},NumComps) ->
     case get_referenced_type(S,V) of
 	{_M,#valuedef{type=_T1,value=V2}} ->
@@ -2253,9 +2259,20 @@ is_record_normalized(S,Name,V = #'Externalvaluereference'{},NumComps) ->
     end;
 is_record_normalized(_S,Name,Value,NumComps) when is_tuple(Value) ->
     (tuple_size(Value) =:= (NumComps + 1)) andalso (element(1, Value) =:= Name);
+is_record_normalized(_S, _Name, Value, _NumComps) when is_map(Value) ->
+    true;
 is_record_normalized(_,_,_,_) ->
     false.
 
+use_maps(#state{options=Opts}) ->
+    lists:member(maps, Opts).
+
+create_map_value(Components, ListOfVals) ->
+    Zipped = lists:zip(Components, ListOfVals),
+    L = [{Name,V} || {#'ComponentType'{name=Name},V} <- Zipped,
+                     V =/= asn1_NOVALUE],
+    maps:from_list(L).
+
 normalize_seq_or_set(SorS, S,
 		     [{#seqtag{val=Cname},V}|Vs],
 		     [#'ComponentType'{name=Cname,typespec=TS}|Cs],
@@ -5674,7 +5691,8 @@ storeindb(S0, #module{name=ModName,typeorval=TVlist0}=M) ->
 
 storeindb_1(S, #module{name=ModName}=M, TVlist0, TVlist) ->
     NewM = M#module{typeorval=findtypes_and_values(TVlist0)},
-    asn1_db:dbnew(ModName, S#state.erule),
+    Maps = lists:member(maps, S#state.options),
+    asn1_db:dbnew(ModName, S#state.erule, Maps),
     asn1_db:dbput(ModName, 'MODULE',  NewM),
     asn1_db:dbput(ModName, TVlist),
     include_default_class(S, NewM#module.name),
diff --git a/lib/asn1/src/asn1ct_constructed_ber_bin_v2.erl b/lib/asn1/src/asn1ct_constructed_ber_bin_v2.erl
index cc1196c5c..16af09bca 100644
--- a/lib/asn1/src/asn1ct_constructed_ber_bin_v2.erl
+++ b/lib/asn1/src/asn1ct_constructed_ber_bin_v2.erl
@@ -57,7 +57,7 @@
 %%===============================================================================
 %%===============================================================================
 
-gen_encode_sequence(Erules,Typename,D) when is_record(D,type) ->
+gen_encode_sequence(Gen, Typename, #type{}=D) ->
     asn1ct_name:start(),
     asn1ct_name:new(term),
     asn1ct_name:new(bytes),
@@ -67,8 +67,12 @@ gen_encode_sequence(Erules,Typename,D) when is_record(D,type) ->
     ValName = 
 	case Typename of
 	    ['EXTERNAL'] ->
+                Tr = case Gen of
+                         #gen{pack=record} -> transform_to_EXTERNAL1990;
+                         #gen{pack=map} -> transform_to_EXTERNAL1990_maps
+                     end,
 		emit([indent(4),"NewVal = ",
-		      {call,ext,transform_to_EXTERNAL1990,["Val"]},
+		      {call,ext,Tr,["Val"]},
 		      com,nl]),
 		"NewVal";
 	    _ ->
@@ -90,18 +94,9 @@ gen_encode_sequence(Erules,Typename,D) when is_record(D,type) ->
 		    {Rl,El} -> Rl ++ El;
 		    _ -> CompList
 		end,
-    
-%% don't match recordname for now, because of compatibility reasons
-%%    emit(["{'",asn1ct_gen:list2rname(Typename),"'"]),
-    emit(["{_"]),
-    case length(CompList1) of
-	0 -> 
-	    true;
-	CompListLen ->
-	    emit([","]),
-	    mkcindexlist([Tc || Tc <- lists:seq(1,CompListLen)])
-    end,
-    emit(["} = ",ValName,",",nl]),
+
+    enc_match_input(Gen, ValName, CompList1),
+
     EncObj =
 	case TableConsInfo of
 	    #simpletableattributes{usedclassfield=Used,
@@ -125,7 +120,7 @@ gen_encode_sequence(Erules,Typename,D) when is_record(D,type) ->
 			emit([ObjectEncode," = ",nl,
 			      "   ",{asis,ObjSetMod},":'getenc_",ObjSetName,
 			      "'("]),
-			ValueMatch = value_match(ValueIndex,
+			ValueMatch = value_match(Gen, ValueIndex,
 						 lists:concat(["Cindex",N])),
 			emit([indent(35),ValueMatch,"),",nl]),
 			{AttrN,ObjectEncode};
@@ -144,7 +139,7 @@ gen_encode_sequence(Erules,Typename,D) when is_record(D,type) ->
 		end
 	end,
 
-    gen_enc_sequence_call(Erules,Typename,CompList1,1,Ext,EncObj),
+    gen_enc_sequence_call(Gen, Typename, CompList1, 1, Ext, EncObj),
 
     emit([nl,"   BytesSoFar = "]),
     case SeqOrSet of
@@ -168,7 +163,36 @@ gen_encode_sequence(Erules,Typename,D) when is_record(D,type) ->
     call(encode_tags, ["TagIn","BytesSoFar","LenSoFar"]),
     emit([".",nl]).
 
-gen_decode_sequence(Erules,Typename,D) when is_record(D,type) ->
+enc_match_input(#gen{pack=record}, ValName, CompList) ->
+    Len = length(CompList),
+    Vars = [lists:concat(["Cindex",N]) || N <- lists:seq(1, Len)],
+    RecordName = "_",
+    emit(["{",lists:join(",", [RecordName|Vars]),"} = ",ValName,com,nl]);
+enc_match_input(#gen{pack=map}, ValName, CompList) ->
+    Len = length(CompList),
+    Vars = [lists:concat(["Cindex",N]) || N <- lists:seq(1, Len)],
+    Zipped = lists:zip(CompList, Vars),
+    M = [[{asis,Name},":=",Var] ||
+            {#'ComponentType'{prop=mandatory,name=Name},Var} <- Zipped],
+    case M of
+        [] ->
+            ok;
+        [_|_] ->
+            emit(["#{",lists:join(",", M),"} = ",ValName,com,nl])
+    end,
+    Os0 = [{Name,Var} ||
+              {#'ComponentType'{prop=Prop,name=Name},Var} <- Zipped,
+              Prop =/= mandatory],
+    F = fun({Name,Var}) ->
+                [Var," = case ",ValName," of\n"
+                 "  #{",{asis,Name},":=",Var,"_0} -> ",
+                 Var,"_0;\n"
+                 "  _ -> ",atom_to_list(?MISSING_IN_MAP),"\n"
+                 "end"]
+        end,
+    emit(lists:join(",\n", [F(E) || E <- Os0]++[[]])).
+
+gen_decode_sequence(Gen, Typename, #type{}=D) ->
     asn1ct_name:start(),
     asn1ct_name:new(tag),
     #'SEQUENCE'{tablecinf=TableConsInfo,components=CList0} = D#type.def,
@@ -225,15 +249,20 @@ gen_decode_sequence(Erules,Typename,D) when is_record(D,type) ->
 	    _ ->
 		{false,false}
 	end,
-    RecordName = lists:concat([get_record_name_prefix(Erules),
-			       asn1ct_gen:list2rname(Typename)]),
-    case gen_dec_sequence_call(Erules,Typename,CompList2,Ext,DecObjInf) of
-	no_terms -> % an empty sequence	    
-	    emit([nl,nl]),
-	    demit(["Result = "]), %dbg
-	    %% return value as record
+    RecordName0 = lists:concat([get_record_name_prefix(Gen),
+                                asn1ct_gen:list2rname(Typename)]),
+    RecordName = list_to_atom(RecordName0),
+    case gen_dec_sequence_call(Gen, Typename, CompList2, Ext, DecObjInf) of
+	no_terms ->                           % an empty sequence
 	    asn1ct_name:new(rb),
-	    emit(["   {'",RecordName,"'}.",nl,nl]);
+            case Gen of
+                #gen{pack=record} ->
+                    emit([nl,nl,
+                          "   {'",RecordName,"'}.",nl,nl]);
+                #gen{pack=map} ->
+                    emit([nl,nl,
+                          "   #{}.",nl,nl])
+            end;
 	{LeadingAttrTerm,PostponedDecArgs} ->
 	    emit([nl]),
 	    case {LeadingAttrTerm,PostponedDecArgs} of
@@ -243,7 +272,7 @@ gen_decode_sequence(Erules,Typename,D) when is_record(D,type) ->
 		    ok;
 		{[{ObjSetRef,LeadingAttr,Term}],PostponedDecArgs} ->
 		    DecObj = asn1ct_gen:un_hyphen_var(lists:concat(['DecObj',LeadingAttr,Term])),
-		    ValueMatch = value_match(ValueIndex,Term),
+		    ValueMatch = value_match(Gen, ValueIndex,Term),
 		    {ObjSetMod,ObjSetName} = ObjSetRef,
 		    emit([DecObj," =",nl,
 			  "   ",{asis,ObjSetMod},":'getdec_",ObjSetName,"'(",
@@ -263,22 +292,64 @@ gen_decode_sequence(Erules,Typename,D) when is_record(D,type) ->
 			  "end,",nl])
 	    end,
 	    asn1ct_name:new(rb),
-	    case Typename of
-		['EXTERNAL'] ->
-		    emit(["   OldFormat={'",RecordName,
-			  "', "]),
-		    mkvlist(asn1ct_name:all(term)),
-		    emit(["},",nl]),
-		    emit(["    ",
-			  {call,ext,transform_to_EXTERNAL1994,
-			   ["OldFormat"]},".",nl]);
-		_ ->
-		    emit(["   {'",RecordName,"', "]),
-		    mkvlist(asn1ct_name:all(term)),
-		    emit(["}.",nl,nl])
-	    end
+            gen_dec_pack(Gen, RecordName, Typename, CompList),
+            emit([".",nl])
     end.
 
+gen_dec_pack(Gen, RecordName, Typename, CompList) ->
+    case Typename of
+	['EXTERNAL'] ->
+            dec_external(Gen, RecordName);
+	_ ->
+            asn1ct_name:new(res),
+            gen_dec_do_pack(Gen, RecordName, CompList),
+            emit([com,nl,
+                  {curr,res}])
+    end.
+
+dec_external(#gen{pack=record}, RecordName) ->
+    All = [{var,Term} || Term <- asn1ct_name:all(term)],
+    Record = [{asis,RecordName}|All],
+    emit(["OldFormat={",lists:join(",", Record),"},",nl,
+          {call,ext,transform_to_EXTERNAL1994,
+           ["OldFormat"]}]);
+dec_external(#gen{pack=map}, _RecordName) ->
+    Vars = asn1ct_name:all(term),
+    Names = ['direct-reference','indirect-reference',
+             'data-value-descriptor',encoding],
+    Zipped = lists:zip(Names, Vars),
+    MapInit = lists:join(",", [["'",N,"'=>",{var,V}] || {N,V} <- Zipped]),
+    emit(["OldFormat = #{",MapInit,"}",com,nl,
+          "ASN11994Format =",nl,
+          {call,ext,transform_to_EXTERNAL1994_maps,
+           ["OldFormat"]}]).
+
+gen_dec_do_pack(#gen{pack=record}, RecordName, _CompList) ->
+    All = asn1ct_name:all(term),
+    L = [{asis,RecordName}|[{var,Var} || Var <- All]],
+    emit([{curr,res}," = {",lists:join(",", L),"}"]);
+gen_dec_do_pack(#gen{pack=map}, _, CompList) ->
+    Zipped = lists:zip(CompList, asn1ct_name:all(term)),
+    PF = fun({#'ComponentType'{prop='OPTIONAL'},_}) -> false;
+            ({_,_}) -> true
+         end,
+    {Mandatory,Optional} = lists:partition(PF, Zipped),
+    L = [[{asis,Name},"=>",{var,Var}] ||
+            {#'ComponentType'{name=Name},Var} <- Mandatory],
+    emit([{curr,res}," = #{",lists:join(",", L),"}"]),
+    gen_dec_map_optional(Optional).
+
+gen_dec_map_optional([{#'ComponentType'{name=Name},Var}|T]) ->
+    asn1ct_name:new(res),
+    emit([com,nl,
+          {curr,res}," = case ",{var,Var}," of",nl,
+          "  asn1_NOVALUE -> ",{prev,res},";",nl,
+          "  _ -> ",{prev,res},"#{",{asis,Name},"=>",{var,Var},"}",nl,
+          "end"]),
+    gen_dec_map_optional(T);
+gen_dec_map_optional([]) ->
+    ok.
+
 gen_dec_postponed_decs(_,[]) ->
     emit(nl);
 gen_dec_postponed_decs(DecObj,[{_Cname,{FirstPFN,PFNList},Term,
@@ -327,7 +398,7 @@ emit_opt_or_mand_check(Value,TmpTerm) ->
 gen_encode_set(Erules,Typename,D) when is_record(D,type) ->
     gen_encode_sequence(Erules,Typename,D).
 
-gen_decode_set(Erules,Typename,D) when is_record(D,type) ->
+gen_decode_set(Gen, Typename, #type{}=D) ->
     asn1ct_name:start(),
 %%    asn1ct_name:new(term),
     asn1ct_name:new(tag),
@@ -393,7 +464,7 @@ gen_decode_set(Erules,Typename,D) when is_record(D,type) ->
 	_ ->
 	    emit(["SetFun = fun(FunTlv) ->", nl]),
 	    emit(["case FunTlv of ",nl]),
-	    NextNum = gen_dec_set_cases(Erules,Typename,CompList,1),
+	    NextNum = gen_dec_set_cases(Gen, Typename, CompList, 1),
 	    emit([indent(6), {curr,else}," -> ",nl,
 		  indent(9),"{",NextNum,", ",{curr,else},"}",nl]),
 	    emit([indent(3),"end",nl]),
@@ -405,14 +476,17 @@ gen_decode_set(Erules,Typename,D) when is_record(D,type) ->
 	    asn1ct_name:new(tlv)
 
     end,
-    RecordName = lists:concat([get_record_name_prefix(Erules),
-			       asn1ct_gen:list2rname(Typename)]),
-    case gen_dec_sequence_call(Erules,Typename,CompList,Ext,DecObjInf) of
-	no_terms -> % an empty sequence	    
-	    emit([nl,nl]),
-	    demit(["Result = "]), %dbg
-	    %% return value as record
-	    emit(["   {'",RecordName,"'}.",nl]);
+    RecordName0 = lists:concat([get_record_name_prefix(Gen),
+                                asn1ct_gen:list2rname(Typename)]),
+    RecordName = list_to_atom(RecordName0),
+    case gen_dec_sequence_call(Gen, Typename, CompList, Ext, DecObjInf) of
+	no_terms ->                           % an empty SET
+            case Gen of
+                #gen{pack=record} ->
+                    emit([nl,nl,"   {'",RecordName,"'}.",nl,nl]);
+                #gen{pack=map} ->
+                    emit([nl,nl,"   #{}.",nl,nl])
+            end;
 	{LeadingAttrTerm,PostponedDecArgs} ->
 	    emit([nl]),
 	    case {LeadingAttrTerm,PostponedDecArgs} of
@@ -422,7 +496,7 @@ gen_decode_set(Erules,Typename,D) when is_record(D,type) ->
 		    ok;
 		{[{ObjSetRef,LeadingAttr,Term}],PostponedDecArgs} ->
 		    DecObj = asn1ct_gen:un_hyphen_var(lists:concat(['DecObj',LeadingAttr,Term])),
-		    ValueMatch = value_match(ValueIndex,Term),
+		    ValueMatch = value_match(Gen, ValueIndex, Term),
 		    {ObjSetMod,ObjSetName} = ObjSetRef,
 		    emit([DecObj," =",nl,
 			  "   ",{asis,ObjSetMod},":'getdec_",ObjSetName,"'(",
@@ -441,9 +515,8 @@ gen_decode_set(Erules,Typename,D) when is_record(D,type) ->
 			  "}}}) % extra fields not allowed",nl,
 			  "end,",nl])
 	    end,
-	    emit(["   {'",RecordName,"', "]),
-	    mkvlist(asn1ct_name:all(term)),
-	    emit(["}.",nl])
+            gen_dec_pack(Gen, RecordName, Typename, CompList),
+	    emit([".",nl])
     end.
 
 
@@ -1025,35 +1098,44 @@ gen_enc_line(Erules,TopType,Cname,Type,Element,Indent,OptOrMand,Assign,EncObj)
 	    emit([nl,indent(7),"end"])
     end.
 
-gen_optormand_case(mandatory, _Erules, _TopType, _Cname, _Type, _Element) ->
+gen_optormand_case(mandatory, _Gen, _TopType, _Cname, _Type, _Element) ->
     ok;
-gen_optormand_case('OPTIONAL', Erules, _TopType, _Cname, _Type, Element) ->
+gen_optormand_case('OPTIONAL', Gen, _TopType, _Cname, _Type, Element) ->
     emit([" case ",Element," of",nl]),
-    emit([indent(9),"asn1_NOVALUE -> {",
-	  empty_lb(Erules),",0};",nl]),
+    Missing = case Gen of
+                  #gen{pack=record} -> asn1_NOVALUE;
+                  #gen{pack=map} -> ?MISSING_IN_MAP
+              end,
+    emit([indent(9),Missing," -> {",
+	  empty_lb(Gen),",0};",nl]),
     emit([indent(9),"_ ->",nl,indent(12)]);
 gen_optormand_case({'DEFAULT',DefaultValue}, Gen, _TopType,
 		   _Cname, Type, Element) ->
     CurrMod = get(currmod),
     case Gen of
         #gen{erule=ber,der=true} ->
-	    asn1ct_gen_check:emit(Type, DefaultValue, Element);
-	#gen{erule=ber,der=false} ->
-	    emit([" case ",Element," of",nl]),
-	    emit([indent(9),"asn1_DEFAULT -> {",
-		  empty_lb(Gen),
-		  ",0};",nl]),
-	    case DefaultValue of 
-		#'Externalvaluereference'{module=CurrMod,
-					  value=V} ->
-		    emit([indent(9),"?",{asis,V}," -> {",
-			  empty_lb(Gen),",0};",nl]);
-		_ ->
-		    emit([indent(9),{asis,
-				     DefaultValue}," -> {",
-			  empty_lb(Gen),",0};",nl])
-	    end,
-	    emit([indent(9),"_ ->",nl,indent(12)])
+	    asn1ct_gen_check:emit(Gen, Type, DefaultValue, Element);
+	#gen{erule=ber,der=false,pack=Pack} ->
+            Ind9 = indent(9),
+            DefMarker = case Pack of
+                            record -> asn1_DEFAULT;
+                            map -> ?MISSING_IN_MAP
+                        end,
+	    emit([" case ",Element," of",nl,
+                  Ind9,{asis,DefMarker}," ->",nl,
+                  Ind9,indent(3),"{",empty_lb(Gen),",0};",nl,
+                  Ind9,"_ when ",Element," =:= "]),
+	    Dv = case DefaultValue of
+                     #'Externalvaluereference'{module=CurrMod,
+                                               value=V} ->
+                         ["?",{asis,V}];
+                     _ ->
+                         [{asis,DefaultValue}]
+                 end,
+            emit(Dv++[" ->",nl,
+                      Ind9,indent(3),"{",empty_lb(Gen),",0};",nl,
+                      Ind9,"_ ->",nl,
+                      indent(12)])
     end.
 
 %% Use for SEQUENCE OF and CHOICE.
@@ -1204,7 +1286,7 @@ gen_dec_call({typefield,_},_,_,Cname,Type,BytesVar,Tag,_,_,_DecObjInf,OptOrMandC
 	(Type#type.def)#'ObjectClassFieldType'.fieldname,
     [{Cname,RefedFieldName,asn1ct_gen:mk_var(asn1ct_name:curr(term)),
       asn1ct_gen:mk_var(asn1ct_name:curr(tmpterm)),Tag,OptOrMandComp}];
-gen_dec_call(InnerType, _Erules, TopType, Cname, Type, BytesVar,
+gen_dec_call(InnerType, Gen, TopType, Cname, Type, BytesVar,
 	     Tag, _PrimOptOrMand, _OptOrMand, DecObjInf,_) ->
     WhatKind = asn1ct_gen:type(InnerType),
     gen_dec_call1(WhatKind, InnerType, TopType, Cname,
@@ -1212,7 +1294,7 @@ gen_dec_call(InnerType, _Erules, TopType, Cname, Type, BytesVar,
     case DecObjInf of
 	{Cname,{_,OSet,_UniqueFName,ValIndex}} ->
 	    Term = asn1ct_gen:mk_var(asn1ct_name:curr(term)),
-	    ValueMatch = value_match(ValIndex,Term),
+	    ValueMatch = value_match(Gen, ValIndex, Term),
 	    {ObjSetMod,ObjSetName} = OSet,
 	    emit([",",nl,"ObjFun = ",{asis,ObjSetMod},":'getdec_",ObjSetName,
 		  "'(",ValueMatch,")"]);
@@ -1337,19 +1419,6 @@ gen_dec_call1(WhatKind, _, TopType, Cname, Type, BytesVar, Tag) ->
 indent(N) ->
     lists:duplicate(N,32). % 32 = space
 
-mkcindexlist([H,T1|T], Sep) -> % Sep is a string e.g ", " or "+ "
-    emit(["Cindex",H,Sep]),
-    mkcindexlist([T1|T], Sep);
-mkcindexlist([H|T], Sep) ->
-    emit(["Cindex",H]),
-    mkcindexlist(T, Sep);
-mkcindexlist([], _) ->
-    true.
-
-mkcindexlist(L) ->
-    mkcindexlist(L,", ").
-
-
 mkvlist([H,T1|T], Sep) -> % Sep is a string e.g ", " or "+ "
     emit([{var,H},Sep]),
     mkvlist([T1|T], Sep);
@@ -1429,16 +1498,22 @@ mkfuncname(TopType,Cname,WhatKind,Prefix,Suffix) ->
 empty_lb(#gen{erule=ber}) ->
     "<<>>".
 
-value_match(Index,Value) when is_atom(Value) ->
-    value_match(Index,atom_to_list(Value));
-value_match([],Value) ->
+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([{VI,_}|VIs],Value) ->
-    value_match1(Value,VIs,lists:concat(["element(",VI,","]),1).
-value_match1(Value,[],Acc,Depth) ->
-    Acc ++ Value ++ lists:concat(lists:duplicate(Depth,")"));
-value_match1(Value,[{VI,_}|VIs],Acc,Depth) ->
-    value_match1(Value,VIs,Acc++lists:concat(["element(",VI,","]),Depth+1).
+value_match_map([{_,Name}|VIs], Value0) ->
+    Value = value_match_map(VIs, Value0),
+    lists:concat(["maps:get(",Name,", ",Value,")"]).
 
 call(F, Args) ->
     asn1ct_func:call(ber, F, Args).
diff --git a/lib/asn1/src/asn1ct_constructed_per.erl b/lib/asn1/src/asn1ct_constructed_per.erl
index e817cf867..b7579c806 100644
--- a/lib/asn1/src/asn1ct_constructed_per.erl
+++ b/lib/asn1/src/asn1ct_constructed_per.erl
@@ -36,6 +36,7 @@
 
 -type type_name() :: any().
 
+
 %% ENCODE GENERATOR FOR SEQUENCE TYPE  ** **********
 
 
@@ -61,29 +62,20 @@ gen_encode_constructed(Erule, Typename, #type{}=D) ->
 
 gen_encode_constructed_imm(Gen, Typename, #type{}=D) ->
     {CompList,TableConsInfo} = enc_complist(D),
-    ExternalImm =
-	case Typename of
-	    ['EXTERNAL'] ->
-		Next = asn1ct_gen:mk_var(asn1ct_name:next(val)),
-		Curr = asn1ct_gen:mk_var(asn1ct_name:curr(val)),
-		asn1ct_name:new(val),
-		[{call,ext,transform_to_EXTERNAL1990,[{var,Curr}],{var,Next}}];
-	    _ ->
-		[]
-	end,
+    ExternalImm = external_imm(Gen, Typename),
     Optionals = optionals(to_textual_order(CompList)),
     ImmOptionals = enc_optionals(Gen, Optionals),
     Ext = extensible_enc(CompList),
     Aligned = is_aligned(Gen),
     ExtImm = case Ext of
 		 {ext,ExtPos,NumExt} when NumExt > 0 ->
-		     gen_encode_extaddgroup(CompList),
+		     gen_encode_extaddgroup(Gen, CompList),
 		     Value = make_var(val),
-		     asn1ct_imm:per_enc_extensions(Value, ExtPos,
-						   NumExt, Aligned);
+                     enc_extensions(Gen, Value, ExtPos, NumExt, Aligned);
 		 _ ->
 		     []
 	     end,
+    MatchImm = enc_map_match(Gen, CompList),
     {EncObj,ObjSetImm} = enc_table(Gen, TableConsInfo, D),
     ImmSetExt =
 	case Ext of
@@ -95,9 +87,29 @@ gen_encode_constructed_imm(Gen, Typename, #type{}=D) ->
 		[]
 	end,
     ImmBody = gen_enc_components_call(Gen, Typename, CompList, EncObj, Ext),
-    ExternalImm ++ ExtImm ++ ObjSetImm ++
+    ExternalImm ++ MatchImm ++ ExtImm ++ ObjSetImm ++
 	asn1ct_imm:enc_append([ImmSetExt] ++ ImmOptionals ++ ImmBody).
 
+external_imm(Gen, ['EXTERNAL']) ->
+    Next = asn1ct_gen:mk_var(asn1ct_name:next(val)),
+    Curr = asn1ct_gen:mk_var(asn1ct_name:curr(val)),
+    asn1ct_name:new(val),
+    F = case Gen of
+            #gen{pack=record} -> transform_to_EXTERNAL1990;
+            #gen{pack=map} -> transform_to_EXTERNAL1990_maps
+        end,
+    [{call,ext,F,[{var,Curr}],{var,Next}}];
+external_imm(_, _) ->
+    [].
+
+enc_extensions(#gen{pack=record}, Value, ExtPos, NumExt, Aligned) ->
+    asn1ct_imm:per_enc_extensions(Value, ExtPos, NumExt, Aligned);
+enc_extensions(#gen{pack=map}, Value, ExtPos, NumExt, Aligned) ->
+    Vars = [{var,lists:concat(["Input@",Pos])} ||
+               Pos <- lists:seq(ExtPos, ExtPos+NumExt-1)],
+    Undefined = atom_to_list(?MISSING_IN_MAP),
+    asn1ct_imm:per_enc_extensions_map(Value, Vars, Undefined, Aligned).
+
 enc_complist(#type{def=Def}) ->
     case Def of
         #'SEQUENCE'{tablecinf=TCI,components=CL0,extaddgroup=ExtAddGroup} ->
@@ -127,7 +139,7 @@ enc_table(Gen, #simpletableattributes{objectsetname=ObjectSet,
         asn1_db:dbget(Module, ObjSetName),
     case MustGen of
         true ->
-            ValueIndex = ValueIndex0 ++ [{N+1,top}],
+            ValueIndex = ValueIndex0 ++ [{N+1,'ASN1_top'}],
             Val = make_var(val),
             {ObjSetImm,Dst} = enc_dig_out_value(Gen, ValueIndex, Val),
             {{AttrN,Dst},ObjSetImm};
@@ -151,41 +163,118 @@ enc_optionals(Gen, Optionals) ->
     Var = make_var(val),
     enc_optionals_1(Gen, Optionals, Var).
 
-enc_optionals_1(Gen, [{Pos,DefVals}|T], Var) ->
+enc_optionals_1(#gen{pack=record}=Gen, [{Pos,DefVals}|T], Var) ->
     {Imm0,Element} = asn1ct_imm:enc_element(Pos+1, Var),
     Imm = asn1ct_imm:per_enc_optional(Element, DefVals),
     [Imm0++Imm|enc_optionals_1(Gen, T, Var)];
+enc_optionals_1(#gen{pack=map}=Gen, [{Pos,DefVals0}|T], V) ->
+    Var = {var,lists:concat(["Input@",Pos])},
+    DefVals = translate_missing_value(Gen, DefVals0),
+    Imm = asn1ct_imm:per_enc_optional(Var, DefVals),
+    [Imm|enc_optionals_1(Gen, T, V)];
 enc_optionals_1(_, [], _) ->
     [].
 
-gen_encode_extaddgroup(CompList) ->
+enc_map_match(#gen{pack=record}, _Cs) ->
+    [];
+enc_map_match(#gen{pack=map}, Cs0) ->
+    Var0 = "Input",
+    Cs = enc_flatten_components(Cs0),
+    M = [[quote_atom(Name),":=",lists:concat([Var0,"@",Order])] ||
+            #'ComponentType'{prop=mandatory,name=Name,
+                             textual_order=Order} <- Cs],
+    Mand = case M of
+               [] ->
+                   [];
+               [_|_] ->
+                   Patt = {expr,lists:flatten(["#{",lists:join(",", M),"}"])},
+                   [{assign,Patt,{var,asn1ct_name:curr(val)}}]
+           end,
+
+    Os0 = [{Name,Order} ||
+              #'ComponentType'{prop=Prop,name=Name,
+                               textual_order=Order} <- Cs,
+              Prop =/= mandatory],
+    {var,Val} = make_var(val),
+    F = fun({Name,Order}) ->
+                Var = lists:concat([Var0,"@",Order]),
+                P0 = ["case ",Val," of\n"
+                      "  #{",quote_atom(Name),":=",Var,"_0} -> ",
+                      Var,"_0;\n"
+                      "  _ -> ",atom_to_list(?MISSING_IN_MAP),"\n"
+                      "end"],
+                P = lists:flatten(P0),
+                {assign,{var,Var},P}
+        end,
+    Os = [F(O) || O <- Os0],
+    Mand ++ Os.
+
+enc_flatten_components({Root1,Ext0,Root2}=CL) ->
+    {_,Gs} = extgroup_pos_and_length(CL),
+    Ext = wrap_extensionAdditionGroups(Ext0, Gs),
+    Root1 ++ Root2 ++ [mark_optional(C) || C <- Ext];
+enc_flatten_components({Root,Ext}) ->
+    enc_flatten_components({Root,Ext,[]});
+enc_flatten_components(Cs) ->
+    Cs.
+
+gen_encode_extaddgroup(#gen{pack=record}, CompList) ->
     case extgroup_pos_and_length(CompList) of
 	{extgrouppos,[]} ->
 	    ok;
 	{extgrouppos,ExtGroupPosLenList} ->
-	    _ = [do_gen_encode_extaddgroup(G) || G <- ExtGroupPosLenList],
+	    _ = [gen_encode_eag_record(G) ||
+                    G <- ExtGroupPosLenList],
 	    ok
-    end.
+    end;
+gen_encode_extaddgroup(#gen{pack=map}, Cs0) ->
+    Cs = enc_flatten_components(Cs0),
+    gen_encode_eag_map(Cs).
+
+gen_encode_eag_map([#'ComponentType'{name=Group,typespec=Type}|Cs]) ->
+    case Type of
+        #type{def=#'SEQUENCE'{extaddgroup=G,components=GCs0}}
+          when is_integer(G) ->
+            Ns = [N || #'ComponentType'{name=N,prop=mandatory} <- GCs0],
+            test_for_mandatory(Ns, Group),
+            gen_encode_eag_map(Cs);
+        _ ->
+            gen_encode_eag_map(Cs)
+    end;
+gen_encode_eag_map([]) ->
+    ok.
 
-do_gen_encode_extaddgroup({ActualGroupPos,GroupVirtualPos,GroupLen}) ->
+test_for_mandatory([Mand|_], Group) ->
+    emit([{next,val}," = case ",{curr,val}," of",nl,
+	  "#{",quote_atom(Mand),":=_} -> ",
+          {curr,val},"#{",{asis,Group},"=>",{curr,val},"};",nl,
+          "#{} -> ",{curr,val},nl,
+	  "end,",nl]),
+    asn1ct_name:new(val);
+test_for_mandatory([], _) ->
+    ok.
+
+gen_encode_eag_record({ActualPos,VirtualPos,Len}) ->
     Val = asn1ct_gen:mk_var(asn1ct_name:curr(val)),
-    Elements = make_elements(GroupVirtualPos+1,
-			     Val,
-			     lists:seq(1, GroupLen)),
-    Expr = any_non_value(GroupVirtualPos+1, Val, GroupLen, ""),
+    Elements = get_input_vars(Val, VirtualPos, Len),
+    Expr = any_non_value(Val, VirtualPos, Len),
     emit([{next,val}," = case ",Expr," of",nl,
-	  "false -> setelement(",{asis,ActualGroupPos+1},", ",
+	  "false -> setelement(",{asis,ActualPos+1},", ",
 	  {curr,val},", asn1_NOVALUE);",nl,
-	  "true -> setelement(",{asis,ActualGroupPos+1},", ",
+	  "true -> setelement(",{asis,ActualPos+1},", ",
 	  {curr,val},", {extaddgroup,", Elements,"})",nl,
 	  "end,",nl]),
     asn1ct_name:new(val).
 
-any_non_value(_, _, 0, _) ->
+any_non_value(Val, Pos, N) ->
+    L = any_non_value_1(Val, Pos, N),
+    lists:join(" orelse ", L).
+
+any_non_value_1(_, _, 0) ->
     [];
-any_non_value(Pos, Val, N, Sep) ->
-    Sep ++ [make_element(Pos, Val)," =/= asn1_NOVALUE"] ++
-	any_non_value(Pos+1, Val, N-1, [" orelse",nl]).
+any_non_value_1(Val, Pos, N) ->
+    Var = get_input_var(Val, Pos),
+    [Var ++ " =/= asn1_NOVALUE"|any_non_value_1(Val, Pos+1, N-1)].
 
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 %% generate decode function for SEQUENCE and SET
@@ -346,27 +435,78 @@ gen_dec_objsets_fun(Gen, ObjSetInfo) ->
     end.
 
 gen_dec_pack(Gen, Typename, CompList) ->
-    RecordName = record_name(Gen, Typename),
     case Typename of
 	['EXTERNAL'] ->
-	    emit({"   OldFormat={'",RecordName,
-		  "'"}),
-	    mkvlist(asn1ct_name:all(term)),
-	    emit({"},",nl}),
-	    emit(["   ASN11994Format =",nl,
-		  "      ",
-		  {call,ext,transform_to_EXTERNAL1994,
-		   ["OldFormat"]},com,nl]),
-	    emit("   {ASN11994Format,");
+            dec_external(Gen, Typename);
 	_ ->
-	    emit(["{{'",RecordName,"'"]),
-	    %% CompList is used here because we don't want
-	    %% ExtensionAdditionGroups to be wrapped in SEQUENCES when
-	    %% we are ordering the fields according to textual order
-	    mkvlist(textual_order(CompList, asn1ct_name:all(term))),
-	    emit("},")
-    end,
-    emit({{curr,bytes},"}"}).
+            asn1ct_name:new(res),
+            gen_dec_do_pack(Gen, Typename, CompList),
+            emit([com,nl,
+                  "{",{curr,res},",",{curr,bytes},"}"])
+    end.
+
+dec_external(#gen{pack=record}=Gen, Typename) ->
+    RecordName = list_to_atom(record_name(Gen, Typename)),
+    All = [{var,Term} || Term <- asn1ct_name:all(term)],
+    Record = [{asis,RecordName}|All],
+    emit(["OldFormat={",lists:join(",", Record),"},",nl,
+          "ASN11994Format =",nl,
+          {call,ext,transform_to_EXTERNAL1994,
+           ["OldFormat"]},com,nl,
+          "{ASN11994Format,",{curr,bytes},"}"]);
+dec_external(#gen{pack=map}, _Typename) ->
+    Vars = asn1ct_name:all(term),
+    Names = ['direct-reference','indirect-reference',
+             'data-value-descriptor',encoding],
+    Zipped = lists:zip(Names, Vars),
+    MapInit = lists:join(",", [["'",N,"'=>",{var,V}] || {N,V} <- Zipped]),
+    emit(["OldFormat = #{",MapInit,"}",com,nl,
+          "ASN11994Format =",nl,
+          {call,ext,transform_to_EXTERNAL1994_maps,
+           ["OldFormat"]},com,nl,
+          "{ASN11994Format,",{curr,bytes},"}"]).
+
+gen_dec_do_pack(#gen{pack=record}=Gen, TypeName, CompList) ->
+    Zipped0 = zip_components(CompList, asn1ct_name:all(term)),
+    Zipped = textual_order(Zipped0),
+    RecordName = ["'",record_name(Gen, TypeName),"'"],
+    L = [RecordName|[{var,Var} || {_,Var} <- Zipped]],
+    emit([{curr,res}," = {",lists:join(",", L),"}"]);
+gen_dec_do_pack(#gen{pack=map}, _, CompList0) ->
+    CompList = enc_flatten_components(CompList0),
+    Zipped0 = zip_components(CompList, asn1ct_name:all(term)),
+    Zipped = textual_order(Zipped0),
+    PF = fun({#'ComponentType'{prop='OPTIONAL'},_}) -> false;
+            ({_,_}) -> true
+         end,
+    {Mandatory,Optional} = lists:partition(PF, Zipped),
+    L = [[{asis,Name},"=>",{var,Var}] ||
+            {#'ComponentType'{name=Name},Var} <- Mandatory],
+    emit([{curr,res}," = #{",lists:join(",", L),"}"]),
+    gen_dec_map_optional(Optional),
+    gen_dec_merge_maps(asn1ct_name:all(map)).
+
+gen_dec_map_optional([{#'ComponentType'{name=Name},Var}|T]) ->
+    asn1ct_name:new(res),
+    emit([com,nl,
+          {curr,res}," = case ",{var,Var}," of",nl,
+          "  asn1_NOVALUE -> ",{prev,res},";",nl,
+          "  _ -> ",{prev,res},"#{",{asis,Name},"=>",{var,Var},"}",nl,
+          "end"]),
+    gen_dec_map_optional(T);
+gen_dec_map_optional([]) ->
+    ok.
+
+gen_dec_merge_maps([M|Ms]) ->
+    asn1ct_name:new(res),
+    emit([com,nl,
+          {curr,res}," = maps:merge(",{prev,res},", ",{var,M},")"]),
+    gen_dec_merge_maps(Ms);
+gen_dec_merge_maps([]) ->
+    ok.
+
+quote_atom(A) when is_atom(A) ->
+    io_lib:format("~p", [A]).
 
 %% record_name([TypeName]) -> RecordNameString
 %%  Construct a record name for the constructed type, ignoring any
@@ -391,16 +531,26 @@ filter_ext_add_groups([H|T], Acc) ->
     filter_ext_add_groups(T, [H|Acc]);
 filter_ext_add_groups([], Acc) -> Acc.
 
-textual_order([#'ComponentType'{textual_order=undefined}|_], TermList) ->
-    TermList;
-textual_order(CompList, TermList) when is_list(CompList) ->
-    OrderList = [Ix||#'ComponentType'{textual_order=Ix} <- CompList],
-    Zipped = lists:sort(lists:zip(OrderList, TermList)),
-    [Term || {_,Term} <- Zipped];
-textual_order({Root,Ext}, TermList) ->
-    textual_order(Root ++ Ext, TermList);
-textual_order({R1,Ext,R2}, TermList) ->
-    textual_order(R1 ++ R2 ++ Ext, TermList).
+zip_components({Root,Ext}, Vars) ->
+    zip_components({Root,Ext,[]}, Vars);
+zip_components({R1,Ext0,R2}, Vars) ->
+    Ext = [mark_optional(C) || C <- Ext0],
+    zip_components(R1++R2++Ext, Vars);
+zip_components(Cs, Vars) when is_list(Cs) ->
+    zip_components_1(Cs, Vars).
+
+zip_components_1([#'ComponentType'{}=C|Cs], [V|Vs]) ->
+    [{C,V}|zip_components_1(Cs, Vs)];
+zip_components_1([_|Cs], Vs) ->
+    zip_components_1(Cs, Vs);
+zip_components_1([], []) ->
+    [].
+
+textual_order([{#'ComponentType'{textual_order=undefined},_}|_]=L) ->
+    L;
+textual_order(L0) ->
+    L = [{Ix,P} || {#'ComponentType'{textual_order=Ix},_}=P <- L0],
+    [C || {_,C} <- lists:sort(L)].
 
 to_textual_order({Root,Ext}) ->
     {to_textual_order(Root),Ext};
@@ -469,7 +619,7 @@ dec_objset_default(N, _, _, true) ->
 	  end]).
 
 dec_objset_1(Erule, N, {Id,Obj}, RestFields, Typename) ->
-    emit([{asis,N},"(Bytes, ",{asis,Id},") ->",nl]),
+    emit([{asis,N},"(Bytes, Id) when Id =:= ",{asis,Id}," ->",nl]),
     dec_objset_2(Erule, Obj, RestFields, Typename).
 
 dec_objset_2(Erule, Obj, RestFields0, Typename) ->
@@ -650,22 +800,7 @@ gen_decode_sof_components(Erule, Name, Typename, SeqOrSetOf, Cont) ->
 
 
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-% General and special help functions (not exported)
-
-mkvlist([H|T]) ->
-    emit(","),
-    mkvlist2([H|T]);
-mkvlist([]) ->
-    true.
-mkvlist2([H,T1|T]) ->
-    emit({{var,H},","}),
-    mkvlist2([T1|T]);
-mkvlist2([H|T]) ->
-    emit({{var,H}}),
-    mkvlist2(T);
-mkvlist2([]) ->
-    true.
-
+%% General and special help functions (not exported)
 
 extensible_dec(CompList) when is_list(CompList) ->
     noext;
@@ -837,32 +972,52 @@ mark_optional(#'ComponentType'{prop=Prop0}=C) ->
                'OPTIONAL'=Keep -> Keep;
                {'DEFAULT',_}=Keep -> Keep
            end,
-    C#'ComponentType'{prop=Prop}.
+    C#'ComponentType'{prop=Prop};
+mark_optional(Other) ->
+    Other.
 
-gen_enc_components_call1(Erule, TopType, [C|Rest], DynamicEnc, Ext) ->
+gen_enc_components_call1(Gen, TopType, [C|Rest], DynamicEnc, Ext) ->
     #'ComponentType'{name=Cname,typespec=Type,
-                     prop=Prop,textual_order=TermNo} = C,
-    Val = make_var(val),
-    {Imm0,Element} = asn1ct_imm:enc_element(TermNo+1, Val),
-    Imm1 = gen_enc_line_imm(Erule, TopType, Cname, Type,
+                     prop=Prop,textual_order=Num} = C,
+    {Imm0,Element} = enc_fetch_field(Gen, Num, Prop),
+    Imm1 = gen_enc_line_imm(Gen, TopType, Cname, Type,
                             Element, DynamicEnc, Ext),
     Imm2 = case Prop of
 	       mandatory ->
 		   Imm1;
 	       'OPTIONAL' ->
-		   asn1ct_imm:enc_absent(Element, [asn1_NOVALUE], Imm1);
+		   enc_absent(Gen, Element, [asn1_NOVALUE], Imm1);
 	       {'DEFAULT',Def} ->
 		   DefValues = def_values(Type, Def),
-		   asn1ct_imm:enc_absent(Element, DefValues, Imm1)
+		   enc_absent(Gen, Element, DefValues, Imm1)
 	   end,
     Imm = case Imm2 of
 	      [] -> [];
 	      _ -> Imm0 ++ Imm2
 	  end,
-    [Imm|gen_enc_components_call1(Erule, TopType, Rest, DynamicEnc, Ext)];
-gen_enc_components_call1(_Erule, _TopType, [], _, _) ->
+    [Imm|gen_enc_components_call1(Gen, TopType, Rest, DynamicEnc, Ext)];
+gen_enc_components_call1(_Gen, _TopType, [], _, _) ->
     [].
 
+enc_absent(Gen, Var, Absent0, Imm) ->
+    Absent = translate_missing_value(Gen, Absent0),
+    asn1ct_imm:enc_absent(Var, Absent, Imm).
+
+translate_missing_value(#gen{pack=record}, Optionals) ->
+    Optionals;
+translate_missing_value(#gen{pack=map}, Optionals) ->
+    case Optionals of
+        [asn1_NOVALUE|T] -> [?MISSING_IN_MAP|T];
+        [asn1_DEFAULT|T] -> [?MISSING_IN_MAP|T];
+        {call,_,_,_} -> Optionals
+    end.
+
+enc_fetch_field(#gen{pack=record}, Num, _Prop) ->
+    Val = make_var(val),
+    asn1ct_imm:enc_element(Num+1, Val);
+enc_fetch_field(#gen{pack=map}, Num, _) ->
+    {[],{var,lists:concat(["Input@",Num])}}.
+
 def_values(#type{def=#'Externaltypereference'{module=Mod,type=Type}}, Def) ->
     #typedef{typespec=T} = asn1_db:dbget(Mod, Type),
     def_values(T, Def);
@@ -1171,7 +1326,7 @@ gen_dec_comp_calls([C|Cs], Erule, TopType, OptTable, DecInfObj,
 gen_dec_comp_calls([], _, _, _, _, _, _, Tpos, Acc) ->
     {lists:append(lists:reverse(Acc)),Tpos}.
 
-gen_dec_comp_call(Comp, Erule, TopType, Tpos, OptTable, DecInfObj,
+gen_dec_comp_call(Comp, Gen, TopType, Tpos, OptTable, DecInfObj,
 		  Ext, NumberOfOptionals) ->
     #'ComponentType'{typespec=Type,prop=Prop,textual_order=TextPos} = Comp,
     Pos = case Ext of
@@ -1212,15 +1367,9 @@ gen_dec_comp_call(Comp, Erule, TopType, Tpos, OptTable, DecInfObj,
 	_ ->
 	    case Type of
 		#type{def=#'SEQUENCE'{
-			extaddgroup=Number1,
-			components=ExtGroupCompList1}} when is_integer(Number1)->
-		    fun(St) ->
-			    emit(["{{_,"]),
-			    emit_extaddgroupTerms(term,ExtGroupCompList1),
-			    emit(["}"]),
-			    emit([",",{next,bytes},"} = "]),
-			    St
-		    end;
+                             extaddgroup=GroupNum,
+                             components=CompList}} when is_integer(GroupNum)->
+                    dec_match_extadd_fun(Gen, CompList);
 		_ ->
 		    fun(St) ->
 			    asn1ct_name:new(term),
@@ -1230,9 +1379,9 @@ gen_dec_comp_call(Comp, Erule, TopType, Tpos, OptTable, DecInfObj,
 		    end
 	    end
 	end,
-    {Pre,Post} = comp_call_pre_post(Ext, Prop, Pos, Type, TextPos,
+    {Pre,Post} = comp_call_pre_post(Gen, Ext, Prop, Pos, Type, TextPos,
 				    OptTable, NumberOfOptionals, Ext),
-    Lines = gen_dec_seq_line_imm(Erule, TopType, Comp, Tpos, DecInfObj, Ext),
+    Lines = gen_dec_seq_line_imm(Gen, TopType, Comp, Tpos, DecInfObj, Ext),
     AdvBuffer = {ignore,fun(St) ->
 				asn1ct_name:new(bytes),
 				St
@@ -1240,9 +1389,24 @@ gen_dec_comp_call(Comp, Erule, TopType, Tpos, OptTable, DecInfObj,
     [{group,[{safe,Comment},{safe,Preamble}] ++ Pre ++
 	  Lines ++ Post ++ [{safe,AdvBuffer}]}].
 
-comp_call_pre_post(noext, mandatory, _, _, _, _, _, _) ->
+dec_match_extadd_fun(#gen{pack=record}, CompList) ->
+    fun(St) ->
+            emit(["{{_,"]),
+            emit_extaddgroupTerms(term, CompList),
+            emit(["}"]),
+            emit([",",{next,bytes},"} = "]),
+            St
+    end;
+dec_match_extadd_fun(#gen{pack=map}, _CompList) ->
+    fun(St) ->
+            asn1ct_name:new(map),
+            emit(["{",{curr,map},",",{next,bytes},"} = "]),
+            St
+    end.
+
+comp_call_pre_post(_Gen, noext, mandatory, _, _, _, _, _, _) ->
     {[],[]};
-comp_call_pre_post(noext, Prop, _, Type, TextPos,
+comp_call_pre_post(_Gen, noext, Prop, _, Type, TextPos,
 		   OptTable, NumOptionals, Ext) ->
     %% OPTIONAL or DEFAULT
     OptPos = get_optionality_pos(TextPos, OptTable),
@@ -1266,32 +1430,53 @@ comp_call_pre_post(noext, Prop, _, Type, TextPos,
 		    "end"]),
 	      St
       end]};
-comp_call_pre_post({ext,_,_}, Prop, Pos, Type, _, _, _, Ext) ->
+comp_call_pre_post(Gen, {ext,_,_}, Prop, Pos, Type, _, _, _, Ext) ->
     %% Extension
     {[fun(St) ->
 	      emit(["case Extensions of",nl,
 		    "  <<_:",Pos-1,",1:1,_/bitstring>> ->",nl]),
 	      St
       end],
-     [fun(St) ->
-	      emit([";",nl,
-		    "_  ->",nl,
-		    "{"]),
-	      case Type of
-		  #type{def=#'SEQUENCE'{
-			       extaddgroup=Number2,
-			       components=ExtGroupCompList2}}
-		    when is_integer(Number2)->
-		      emit("{extAddGroup,"),
-		      gen_dec_extaddGroup_no_val(Ext, Type, ExtGroupCompList2),
-		      emit("}");
-		  _ ->
-		      gen_dec_component_no_val(Ext, Type, Prop)
-	      end,
-	      emit([",",{curr,bytes},"}",nl,
-		    "end"]),
-	      St
-      end]}.
+     [extadd_group_fun(Gen, Prop, Type, Ext)]}.
+
+extadd_group_fun(#gen{pack=record}, Prop, Type, Ext) ->
+    fun(St) ->
+            emit([";",nl,
+                  "_  ->",nl,
+                  "{"]),
+            case Type of
+                #type{def=#'SEQUENCE'{
+                             extaddgroup=Number2,
+                             components=ExtGroupCompList2}}
+                  when is_integer(Number2)->
+                    emit("{extAddGroup,"),
+                    gen_dec_extaddGroup_no_val(Ext, Type, ExtGroupCompList2),
+                    emit("}");
+                _ ->
+                    gen_dec_component_no_val(Ext, Type, Prop)
+            end,
+            emit([",",{curr,bytes},"}",nl,
+                  "end"]),
+            St
+    end;
+extadd_group_fun(#gen{pack=map}, Prop, Type, Ext) ->
+    fun(St) ->
+            emit([";",nl,
+                  "_  ->",nl,
+                  "{"]),
+            case Type of
+                #type{def=#'SEQUENCE'{
+                             extaddgroup=Number2,
+                             components=Comp}}
+                  when is_integer(Number2)->
+                    dec_map_extaddgroup_no_val(Ext, Type, Comp);
+                _ ->
+                    gen_dec_component_no_val(Ext, Type, Prop)
+            end,
+            emit([",",{curr,bytes},"}",nl,
+                  "end"]),
+            St
+    end.
 
 is_mandatory_predef_tab_c(noext, mandatory,
 			  {"got objfun through args","ObjFun"}) ->
@@ -1318,7 +1503,20 @@ gen_dec_component_no_val(_, _, 'OPTIONAL') ->
     emit({"asn1_NOVALUE"});
 gen_dec_component_no_val({ext,_,_}, _, mandatory) ->
     emit({"asn1_NOVALUE"}).
-    
+
+dec_map_extaddgroup_no_val(Ext, Type, Comp) ->
+    L0 = [dec_map_extaddgroup_no_val_1(N, P, Ext, Type) ||
+             #'ComponentType'{name=N,prop=P} <- Comp],
+    L = [E || E <- L0, E =/= []],
+    emit(["#{",lists:join(",", L),"}"]).
+
+dec_map_extaddgroup_no_val_1(Name, {'DEFAULT',DefVal0}, _Ext, Type) ->
+    DefVal = asn1ct_gen:conform_value(Type, DefVal0),
+    [Name,"=>",{asis,DefVal}];
+dec_map_extaddgroup_no_val_1(_Name, 'OPTIONAL', _, _) ->
+    [];
+dec_map_extaddgroup_no_val_1(_Name, mandatory, {ext,_,_}, _) ->
+    [].
 
 gen_dec_choice_line(Erule, TopType, Comp, Pre) ->
     Imm0 = gen_dec_line_imm(Erule, TopType, Comp, false, Pre),
@@ -1698,20 +1896,17 @@ gen_dec_choice2(Erule, TopType, [H0|T], Pos, Sep0, Pre) ->
     gen_dec_choice2(Erule, TopType, T, Pos+1, Sep, Pre);
 gen_dec_choice2(_, _, [], _, _, _)  -> ok.
 
-make_elements(I,Val,ExtCnames) ->
-    make_elements(I,Val,ExtCnames,[]).
+get_input_vars(Val, I, N) ->
+    L = get_input_vars_1(Val, I, N),
+    lists:join(",", L).
 
-make_elements(I,Val,[_ExtCname],Acc)-> % the last one, no comma needed
-    Element = make_element(I, Val),
-    make_elements(I+1,Val,[],[Element|Acc]);
-make_elements(I,Val,[_ExtCname|Rest],Acc)->
-    Element = make_element(I, Val),
-    make_elements(I+1,Val,Rest,[", ",Element|Acc]);
-make_elements(_I,_,[],Acc) ->
-    lists:reverse(Acc).
+get_input_vars_1(_Val, _I, 0) ->
+    [];
+get_input_vars_1(Val, I, N) ->
+    [get_input_var(Val, I)|get_input_vars_1(Val, I+1, N-1)].
 
-make_element(I, Val) ->
-    lists:flatten(io_lib:format("element(~w, ~s)", [I,Val])).
+get_input_var(Val, I) ->
+    lists:flatten(io_lib:format("element(~w, ~s)", [I+1,Val])).
 
 emit_extaddgroupTerms(VarSeries,[_]) ->
     asn1ct_name:new(VarSeries),
@@ -1728,57 +1923,66 @@ flat_complist({Rl1,El,Rl2}) -> Rl1 ++ El ++ Rl2;
 flat_complist({Rl,El}) -> Rl ++ El;
 flat_complist(CompList) -> CompList.
 
-%%wrap_compList({Root1,Ext,Root2}) ->
-%%    {Root1,wrap_extensionAdditionGroups(Ext),Root2};
-%%wrap_compList({Root1,Ext}) ->
-%%    {Root1,wrap_extensionAdditionGroups(Ext)};
-%%wrap_compList(CompList) ->
-%%    CompList.
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
-%%  Will convert all componentTypes following 'ExtensionAdditionGroup'
+%%  Convert all componentTypes following 'ExtensionAdditionGroup'
 %%  up to the matching 'ExtensionAdditionGroupEnd' into one componentType
-%% of type SEQUENCE with the componentTypes as components
+%%  of type SEQUENCE with the componentTypes as components.
 %%
-wrap_extensionAdditionGroups(ExtCompList,ExtGroupPosLen) ->
-    wrap_extensionAdditionGroups(ExtCompList,ExtGroupPosLen,[],0,0).
+wrap_extensionAdditionGroups(ExtCompList, ExtGroupPosLen) ->
+    wrap_eags(ExtCompList, ExtGroupPosLen, 0, 0).
 
-wrap_extensionAdditionGroups([{'ExtensionAdditionGroup',_Number}|Rest],
-			     [{ActualPos,_,_}|ExtGroupPosLenRest],Acc,_ExtAddGroupDiff,ExtGroupNum) ->
-    {ExtGroupCompList,['ExtensionAdditionGroupEnd'|Rest2]} =
+wrap_eags([{'ExtensionAdditionGroup',_Number}|T0],
+          [{ActualPos,_,_}|Gs], _ExtAddGroupDiff, ExtGroupNum) ->
+    {ExtGroupCompList,['ExtensionAdditionGroupEnd'|T]} =
 	lists:splitwith(fun(#'ComponentType'{}) -> true;
 			   (_) -> false
-			end,
-			Rest),
-    wrap_extensionAdditionGroups(Rest2,ExtGroupPosLenRest,
-				 [#'ComponentType'{
-				     name=list_to_atom("ExtAddGroup"++
-							integer_to_list(ExtGroupNum+1)), 
-				     typespec=#type{def=#'SEQUENCE'{
-						   extaddgroup=ExtGroupNum+1,
-						   components=ExtGroupCompList}},
-				     textual_order = ActualPos,
-				     prop='OPTIONAL'}|Acc],length(ExtGroupCompList)-1,
-				 ExtGroupNum+1);
-wrap_extensionAdditionGroups([H=#'ComponentType'{textual_order=Tord}|T],
-			     ExtAddGrpLenPos,Acc,ExtAddGroupDiff,ExtGroupNum) when is_integer(Tord) ->
-    wrap_extensionAdditionGroups(T,ExtAddGrpLenPos,[H#'ComponentType'{
-				      textual_order=Tord - ExtAddGroupDiff}|Acc],ExtAddGroupDiff,ExtGroupNum);
-wrap_extensionAdditionGroups([H|T],ExtAddGrpLenPos,Acc,ExtAddGroupDiff,ExtGroupNum) ->
-    wrap_extensionAdditionGroups(T,ExtAddGrpLenPos,[H|Acc],ExtAddGroupDiff,ExtGroupNum);
-wrap_extensionAdditionGroups([],_,Acc,_,_) ->
-    lists:reverse(Acc).
-
-value_match(_Gen, [], Value) ->
+			end, T0),
+    Name = list_to_atom(lists:concat(["ExtAddGroup",ExtGroupNum+1])),
+    Seq = #type{def=#'SEQUENCE'{extaddgroup=ExtGroupNum+1,
+                                components=ExtGroupCompList}},
+    Comp = #'ComponentType'{name=Name,
+                            typespec=Seq,
+                            textual_order=ActualPos,
+                            prop='OPTIONAL'},
+    [Comp|wrap_eags(T, Gs, length(ExtGroupCompList)-1, ExtGroupNum+1)];
+wrap_eags([#'ComponentType'{textual_order=Tord}=H|T],
+          ExtAddGrpLenPos, ExtAddGroupDiff, ExtGroupNum)
+  when is_integer(Tord) ->
+    Comp = H#'ComponentType'{textual_order=Tord - ExtAddGroupDiff},
+    [Comp|wrap_eags(T, ExtAddGrpLenPos, ExtAddGroupDiff, ExtGroupNum)];
+wrap_eags([H|T], ExtAddGrpLenPos, ExtAddGroupDiff, ExtGroupNum) ->
+    [H|wrap_eags(T, ExtAddGrpLenPos, ExtAddGroupDiff, ExtGroupNum)];
+wrap_eags([], _, _, _) ->
+    [].
+
+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(Gen, [{VI,_}|VIs], Value0) ->
-    Value = value_match(Gen, VIs, Value0),
+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,")"]).
+
 enc_dig_out_value(_Gen, [], Value) ->
     {[],Value};
-enc_dig_out_value(Gen, [{N,_}|T], Value) ->
+enc_dig_out_value(#gen{pack=record}=Gen, [{N,_}|T], Value) ->
     {Imm0,Dst0} = enc_dig_out_value(Gen, T, Value),
     {Imm,Dst} = asn1ct_imm:enc_element(N, Dst0),
+    {Imm0++Imm,Dst};
+enc_dig_out_value(#gen{pack=map}, [{N,'ASN1_top'}], _Value) ->
+    {[],{var,lists:concat(["Input@",N-1])}};
+enc_dig_out_value(#gen{pack=map}=Gen, [{_,Name}|T], Value) ->
+    {Imm0,Dst0} = enc_dig_out_value(Gen, T, Value),
+    {Imm,Dst} = asn1ct_imm:enc_maps_get(Name, Dst0),
     {Imm0++Imm,Dst}.
 
 make_var(Base) ->
diff --git a/lib/asn1/src/asn1ct_eval_ext.funcs b/lib/asn1/src/asn1ct_eval_ext.funcs
index 5761901f8..01c67e7b5 100644
--- a/lib/asn1/src/asn1ct_eval_ext.funcs
+++ b/lib/asn1/src/asn1ct_eval_ext.funcs
@@ -1 +1,2 @@
 {ext,transform_to_EXTERNAL1994,1}.
+{ext,transform_to_EXTERNAL1994_maps,1}.
diff --git a/lib/asn1/src/asn1ct_gen.erl b/lib/asn1/src/asn1ct_gen.erl
index a54cb0765..4fa830d7d 100644
--- a/lib/asn1/src/asn1ct_gen.erl
+++ b/lib/asn1/src/asn1ct_gen.erl
@@ -67,6 +67,7 @@ pgen(OutFile, #gen{options=Options}=Gen, Module, Contents) ->
 		   UnmatchedTypes})
     end,
     put(outfile,OutFile),
+    put(currmod, Module),
     HrlGenerated = pgen_hrl(Gen, Module, Contents),
     asn1ct_name:start(),
     ErlFile = lists:concat([OutFile,".erl"]),
@@ -650,7 +651,7 @@ gen_decode_constructed(Erules,Typename,InnerType,D) when is_record(D,typedef) ->
 
 pgen_exports(#gen{options=Options}=Gen, _Module, Contents) ->
     {Types,Values,_,_,Objects,ObjectSets} = Contents,
-    emit(["-export([encoding_rule/0,bit_string_format/0,",nl,
+    emit(["-export([encoding_rule/0,maps/0,bit_string_format/0,",nl,
 	  "         legacy_erlang_types/0]).",nl]),
     emit(["-export([",{asis,?SUPPRESSION_FUNC},"/1]).",nl]),
     case Types of
@@ -887,8 +888,14 @@ gen_info_functions(Gen) ->
                 #gen{erule=per,aligned=false} -> uper;
                 #gen{erule=per,aligned=true} -> per
             end,
+    Maps = case Gen of
+               #gen{pack=record} -> false;
+               #gen{pack=map} -> true
+           end,
     emit(["encoding_rule() -> ",
 	  {asis,Erule},".",nl,nl,
+          "maps() -> ",
+          {asis,Maps},".",nl,nl,
 	  "bit_string_format() -> ",
 	  {asis,asn1ct:get_bit_string_format()},".",nl,nl,
 	  "legacy_erlang_types() -> ",
@@ -1093,8 +1100,7 @@ open_output_file(F) ->
 close_output_file() ->
     ok = file:close(erase(gen_file_out)).
 
-pgen_hrl(Gen, Module, Contents) ->
-    put(currmod, Module),
+pgen_hrl(#gen{pack=record}=Gen, Module, Contents) ->
     {Types,Values,Ptypes,_,_,_} = Contents,
     Ret =
 	case pgen_hrltypes(Gen, Module, Ptypes++Types, 0) of
@@ -1103,7 +1109,7 @@ pgen_hrl(Gen, Module, Contents) ->
 		    [] ->
 			0;
 		    _ ->
-			open_hrl(get(outfile),get(currmod)),
+			open_hrl(get(outfile), Module),
 			pgen_macros(Gen, Module, Values),
 			1
 		end;
@@ -1122,7 +1128,9 @@ pgen_hrl(Gen, Module, Contents) ->
 			   [{generated,lists:concat([get(outfile),".hrl"])}],
 			   Gen),
 	    Y
-    end.
+    end;
+pgen_hrl(#gen{pack=map}, _, _) ->
+    0.
 
 pgen_macros(_,_,[]) ->
     true;
diff --git a/lib/asn1/src/asn1ct_gen_ber_bin_v2.erl b/lib/asn1/src/asn1ct_gen_ber_bin_v2.erl
index b884d14b0..6c6d4193f 100644
--- a/lib/asn1/src/asn1ct_gen_ber_bin_v2.erl
+++ b/lib/asn1/src/asn1ct_gen_ber_bin_v2.erl
@@ -1200,11 +1200,13 @@ gen_objset_enc(Erules, ObjSetName, UniqueName,
 	    {no_mod,no_name} ->
 		gen_inlined_enc_funs(Fields, ClFields, ObjSetName, Val, NthObj);
 	    {CurrMod,Name} ->
-		emit(["'getenc_",ObjSetName,"'(",{asis,Val},") ->",nl,
+		emit(["'getenc_",ObjSetName,"'(Id) when Id =:= ",
+                      {asis,Val}," ->",nl,
 		      "    fun 'enc_",Name,"'/3;",nl]),
 		{[],NthObj};
 	    {ModuleName,Name} ->
-		emit(["'getenc_",ObjSetName,"'(",{asis,Val},") ->",nl]),
+		emit(["'getenc_",ObjSetName,"'(Id) when Id =:= ",
+                      {asis,Val}," ->",nl]),
 		emit_ext_fun(enc,ModuleName,Name),
 		emit([";",nl]),
 		{[],NthObj};
@@ -1382,11 +1384,13 @@ gen_objset_dec(Erules, ObjSName, UniqueName, [{ObjName,Val,Fields}|T],
 	    {no_mod,no_name} ->
 		gen_inlined_dec_funs(Fields,ClFields,ObjSName,Val,NthObj);
 	    {CurrMod,Name} ->
-		emit(["'getdec_",ObjSName,"'(",{asis,Val},") ->",nl,
+		emit(["'getdec_",ObjSName,"'(Id) when Id =:= ",
+                      {asis,Val}," ->",nl,
 		      "    fun 'dec_",Name,"'/3;", nl]),
 		NthObj;
 	    {ModuleName,Name} ->
-		emit(["'getdec_",ObjSName,"'(",{asis,Val},") ->",nl]),
+		emit(["'getdec_",ObjSName,"'(Id) when Id =:= ",
+                      {asis,Val}," ->",nl]),
 		emit_ext_fun(dec,ModuleName,Name),
 		emit([";",nl]),
 		NthObj;
diff --git a/lib/asn1/src/asn1ct_gen_check.erl b/lib/asn1/src/asn1ct_gen_check.erl
index abe77dd0c..ccc62a3ce 100644
--- a/lib/asn1/src/asn1ct_gen_check.erl
+++ b/lib/asn1/src/asn1ct_gen_check.erl
@@ -21,45 +21,51 @@
 %%
 
 -module(asn1ct_gen_check).
--export([emit/3]).
+-export([emit/4]).
 
 -import(asn1ct_gen, [emit/1]).
 -include("asn1_records.hrl").
 
-emit(Type, Default, Value) ->
+emit(Gen, Type, Default, Value) ->
     Key = {Type,Default},
-    Gen = fun(Fd, Name) ->
-		  file:write(Fd, gen(Name, Type, Default))
-	  end,
+    DoGen = fun(Fd, Name) ->
+                    file:write(Fd, gen(Gen, Name, Type, Default))
+            end,
     emit(" case "),
-    asn1ct_func:call_gen("is_default_", Key, Gen, [Value]),
+    asn1ct_func:call_gen("is_default_", Key, DoGen, [Value]),
     emit([" of",nl,
 	  "true -> {[],0};",nl,
 	  "false ->",nl]).
 
-gen(Name, #type{def=T}, Default) ->
+gen(#gen{pack=Pack}=Gen, Name, #type{def=T}, Default) ->
+    DefMarker = case Pack of
+                    record -> "asn1_DEFAULT";
+                    map -> atom_to_list(?MISSING_IN_MAP)
+                end,
     NameStr = atom_to_list(Name),
-    [NameStr,"(asn1_DEFAULT) ->\n",
-     "true;\n"|case do_gen(T, Default) of
-		   {literal,Literal} ->
-		       [NameStr,"(",term2str(Literal),") ->\n","true;\n",
-			NameStr,"(_) ->\n","false.\n\n"];
-		   {exception,Func,Args} ->
-		       [NameStr,"(Value) ->\n",
-			"try ",Func,"(Value",arg2str(Args),") of\n",
-			"_ -> true\n"
-			"catch throw:false -> false\n"
-			"end.\n\n"]
-	       end].
+    [NameStr,"(",DefMarker,") ->\n",
+     "true;\n"|
+     case do_gen(Gen, T, Default) of
+         {literal,Literal} ->
+             [NameStr,"(Def) when Def =:= ",term2str(Literal)," ->\n",
+              "true;\n",
+              NameStr,"(_) ->\n","false.\n\n"];
+         {exception,Func,Args} ->
+             [NameStr,"(Value) ->\n",
+              "try ",Func,"(Value",arg2str(Args),") of\n",
+              "_ -> true\n"
+              "catch throw:false -> false\n"
+              "end.\n\n"]
+     end].
 
-do_gen(_, asn1_NOVALUE) ->
+do_gen(_Gen, _, asn1_NOVALUE) ->
     {literal,asn1_NOVALUE};
-do_gen(#'Externaltypereference'{module=M,type=T}, Default) ->
+do_gen(Gen, #'Externaltypereference'{module=M,type=T}, Default) ->
     #typedef{typespec=#type{def=Td}} = asn1_db:dbget(M, T),
-    do_gen(Td, Default);
-do_gen('BOOLEAN', Default) ->
+    do_gen(Gen, Td, Default);
+do_gen(_Gen, 'BOOLEAN', Default) ->
     {literal,Default};
-do_gen({'BIT STRING',[]}, Default) ->
+do_gen(_Gen, {'BIT STRING',[]}, Default) ->
     true = is_bitstring(Default),		%Assertion.
     case asn1ct:use_legacy_types() of
 	false ->
@@ -67,17 +73,17 @@ do_gen({'BIT STRING',[]}, Default) ->
 	true ->
 	    {exception,need(check_legacy_bitstring, 2),[Default]}
     end;
-do_gen({'BIT STRING',[_|_]=NBL}, Default) ->
+do_gen(_Gen, {'BIT STRING',[_|_]=NBL}, Default) ->
     do_named_bitstring(NBL, Default);
-do_gen({'ENUMERATED',_}, Default) ->
+do_gen(_Gen, {'ENUMERATED',_}, Default) ->
     {literal,Default};
-do_gen('INTEGER', Default) ->
+do_gen(_Gen, 'INTEGER', Default) ->
     {literal,Default};
-do_gen({'INTEGER',NNL}, Default) ->
+do_gen(_Gen, {'INTEGER',NNL}, Default) ->
     {exception,need(check_int, 3),[Default,NNL]};
-do_gen('NULL', Default) ->
+do_gen(_Gen, 'NULL', Default) ->
     {literal,Default};
-do_gen('OCTET STRING', Default) ->
+do_gen(_Gen, 'OCTET STRING', Default) ->
     true = is_binary(Default),			%Assertion.
     case asn1ct:use_legacy_types() of
 	false ->
@@ -85,34 +91,34 @@ do_gen('OCTET STRING', Default) ->
 	true ->
 	    {exception,need(check_octetstring, 2),[Default]}
     end;
-do_gen('OBJECT IDENTIFIER', Default0) ->
+do_gen(_Gen, 'OBJECT IDENTIFIER', Default0) ->
     Default = pre_process_oid(Default0),
     {exception,need(check_objectidentifier, 2),[Default]};
-do_gen({'CHOICE',Cs}, Default) ->
+do_gen(Gen, {'CHOICE',Cs}, Default) ->
     {Tag,Value} = Default,
     [Type] = [Type || #'ComponentType'{name=T,typespec=Type} <- Cs,
 		      T =:= Tag],
-    case do_gen(Type#type.def, Value) of
+    case do_gen(Gen, Type#type.def, Value) of
 	{literal,Lit} ->
 	    {literal,{Tag,Lit}};
 	{exception,Func0,Args} ->
 	    Key = {Tag,Func0,Args},
-	    Gen = fun(Fd, Name) ->
-			  S = gen_choice(Name, Tag, Func0, Args),
-			  ok = file:write(Fd, S)
+	    DoGen = fun(Fd, Name) ->
+                            S = gen_choice(Name, Tag, Func0, Args),
+                            ok = file:write(Fd, S)
 		  end,
-	    Func = asn1ct_func:call_gen("is_default_choice", Key, Gen),
+	    Func = asn1ct_func:call_gen("is_default_choice", Key, DoGen),
 	    {exception,atom_to_list(Func),[]}
     end;
-do_gen(#'SEQUENCE'{components=Cs}, Default) ->
-    do_seq_set(Cs, Default);
-do_gen({'SEQUENCE OF',Type}, Default) ->
-    do_sof(Type, Default);
-do_gen(#'SET'{components=Cs}, Default) ->
-    do_seq_set(Cs, Default);
-do_gen({'SET OF',Type}, Default) ->
-    do_sof(Type, Default);
-do_gen(Type, Default) ->
+do_gen(Gen, #'SEQUENCE'{components=Cs}, Default) ->
+    do_seq_set(Gen, Cs, Default);
+do_gen(Gen, {'SEQUENCE OF',Type}, Default) ->
+    do_sof(Gen, Type, Default);
+do_gen(Gen, #'SET'{components=Cs}, Default) ->
+    do_seq_set(Gen, Cs, Default);
+do_gen(Gen, {'SET OF',Type}, Default) ->
+    do_sof(Gen, Type, Default);
+do_gen(_Gen, Type, Default) ->
     case asn1ct_gen:unify_if_string(Type) of
 	restrictedstring ->
 	    {exception,need(check_restrictedstring, 2),[Default]};
@@ -136,39 +142,58 @@ do_named_bitstring(_, Default) when is_bitstring(Default) ->
 	   end,
     {exception,need(Func, 3),[Default,bit_size(Default)]}.
 
-do_seq_set(Cs0, Default) ->
+do_seq_set(#gen{pack=record}=Gen, Cs0, Default) ->
     Tag = element(1, Default),
     Cs1 = [T || #'ComponentType'{typespec=T} <- Cs0],
-    Cs = components(Cs1, tl(tuple_to_list(Default))),
+    Cs = components(Gen, Cs1, tl(tuple_to_list(Default))),
     case are_all_literals(Cs) of
 	true ->
 	    Literal = list_to_tuple([Tag|[L || {literal,L} <- Cs]]),
 	    {literal,Literal};
 	false ->
 	    Key = {Cs,Default},
-	    Gen = fun(Fd, Name) ->
-			  S = gen_components(Name, Tag, Cs),
-			  ok = file:write(Fd, S)
-		  end,
-	    Func = asn1ct_func:call_gen("is_default_cs_", Key, Gen),
+	    DoGen = fun(Fd, Name) ->
+                            S = gen_components(Name, Tag, Cs),
+                            ok = file:write(Fd, S)
+                    end,
+	    Func = asn1ct_func:call_gen("is_default_cs_", Key, DoGen),
+	    {exception,atom_to_list(Func),[]}
+    end;
+do_seq_set(#gen{pack=map}=Gen, Cs0, Default) ->
+    Cs1 = [{N,T} || #'ComponentType'{name=N,typespec=T} <- Cs0],
+    Cs = map_components(Gen, Cs1, Default),
+    AllLiterals = lists:all(fun({_,{literal,_}}) -> true;
+                               ({_,_}) -> false
+                            end, Cs),
+    case AllLiterals of
+	true ->
+            L = [{Name,Lit} || {Name,{literal,Lit}} <- Cs],
+	    {literal,maps:from_list(L)};
+	false ->
+	    Key = {Cs,Default},
+	    DoGen = fun(Fd, Name) ->
+                            S = gen_map_components(Name, Cs),
+                            ok = file:write(Fd, S)
+                    end,
+	    Func = asn1ct_func:call_gen("is_default_cs_", Key, DoGen),
 	    {exception,atom_to_list(Func),[]}
     end.
 
-do_sof(Type, Default0) ->
+do_sof(Gen, Type, Default0) ->
     Default = lists:sort(Default0),
     Cs0 = lists:duplicate(length(Default), Type),
-    Cs = components(Cs0, Default),
+    Cs = components(Gen, Cs0, Default),
     case are_all_literals(Cs) of
 	true ->
 	    Literal = [Lit || {literal,Lit} <- Cs],
 	    {exception,need(check_literal_sof, 2),[Literal]};
 	false ->
 	    Key = Cs,
-	    Gen = fun(Fd, Name) ->
-			  S = gen_sof(Name, Cs),
-			  ok = file:write(Fd, S)
+	    DoGen = fun(Fd, Name) ->
+                            S = gen_sof(Name, Cs),
+                            ok = file:write(Fd, S)
 		  end,
-	    Func = asn1ct_func:call_gen("is_default_sof", Key, Gen),
+	    Func = asn1ct_func:call_gen("is_default_sof", Key, DoGen),
 	    {exception,atom_to_list(Func),[]}
     end.
 
@@ -199,6 +224,39 @@ gen_cs_2([], _) ->
      "throw(false)\n"
      "end.\n"].
 
+gen_map_components(Name, Cs) ->
+    [atom_to_list(Name),"(Value) ->\n",
+     "case Value of\n",
+     "#{"|gen_map_cs_1(Cs, 1, "", [])].
+
+gen_map_cs_1([{Name,{literal,Lit}}|T], I, Sep, Acc) ->
+    Var = "E"++integer_to_list(I),
+    G = Var ++ " =:= " ++ term2str(Lit),
+    [Sep,term2str(Name),":=",Var|
+     gen_map_cs_1(T, I+1, ",\n", [{guard,G}|Acc])];
+gen_map_cs_1([{Name,Exc}|T], I, Sep, Acc) ->
+    Var = "E"++integer_to_list(I),
+    [Sep,term2str(Name),":=",Var|
+     gen_map_cs_1(T, I+1, ",\n", [{exc,{Var,Exc}}|Acc])];
+gen_map_cs_1([], _, _, Acc) ->
+    G = lists:join(", ", [S || {guard,S} <- Acc]),
+    Exc = [E || {exc,E} <- Acc],
+    Body = gen_map_cs_2(Exc, ""),
+    case G of
+        [] ->
+            ["} ->\n"|Body];
+        [_|_] ->
+            ["} when ",G," ->\n"|Body]
+    end.
+
+gen_map_cs_2([{Var,{exception,Func,Args}}|T], Sep) ->
+    [Sep,Func,"(",Var,arg2str(Args),")"|gen_map_cs_2(T, ",\n")];
+gen_map_cs_2([], _) ->
+    [";\n",
+     "_ ->\n"
+     "throw(false)\n"
+     "end.\n"].
+
 gen_sof(Name, Cs) ->
     [atom_to_list(Name),"(Value) ->\n",
      "case length(Value) of\n",
@@ -221,9 +279,18 @@ gen_sof_1([{exception,Func,Args}|Cs], I) ->
 gen_sof_1([], _) ->
     ".\n".
 
-components([#type{def=Def}|Ts], [V|Vs]) ->
-    [do_gen(Def, V)|components(Ts, Vs)];
-components([], []) -> [].
+components(Gen, [#type{def=Def}|Ts], [V|Vs]) ->
+    [do_gen(Gen, Def, V)|components(Gen, Ts, Vs)];
+components(_Gen, [], []) -> [].
+
+map_components(Gen, [{Name,#type{def=Def}}|Ts], Value) ->
+    case maps:find(Name, Value) of
+        {ok,V} ->
+            [{Name,do_gen(Gen, Def, V)}|map_components(Gen, Ts, Value)];
+        error ->
+            map_components(Gen, Ts, Value)
+    end;
+map_components(_Gen, [], _Value) -> [].
 
 gen_choice(Name, Tag, Func, Args) ->
     NameStr = atom_to_list(Name),
diff --git a/lib/asn1/src/asn1ct_imm.erl b/lib/asn1/src/asn1ct_imm.erl
index 741d54c32..2ab848652 100644
--- a/lib/asn1/src/asn1ct_imm.erl
+++ b/lib/asn1/src/asn1ct_imm.erl
@@ -37,9 +37,11 @@
 	 per_enc_open_type/2,
 	 per_enc_restricted_string/3,
 	 per_enc_small_number/2]).
--export([per_enc_extension_bit/2,per_enc_extensions/4,per_enc_optional/2]).
+-export([per_enc_extension_bit/2,per_enc_extensions/4,
+         per_enc_extensions_map/4,
+         per_enc_optional/2]).
 -export([per_enc_sof/5]).
--export([enc_absent/3,enc_append/1,enc_element/2]).
+-export([enc_absent/3,enc_append/1,enc_element/2,enc_maps_get/2]).
 -export([enc_cg/2]).
 -export([optimize_alignment/1,optimize_alignment/2,
 	 dec_slim_cg/2,dec_code_gen/2]).
@@ -349,6 +351,20 @@ per_enc_extensions(Val0, Pos0, NumBits, Aligned) when NumBits > 0 ->
 			['_'|Length ++ PutBits]]}],
 	 {var,"Extensions"}}].
 
+per_enc_extensions_map(Val0, Vars, Undefined, Aligned) ->
+    NumBits = length(Vars),
+    {B,[_Val,Bitmap]} = mk_vars(Val0, [bitmap]),
+    Length = per_enc_small_length(NumBits, Aligned),
+    PutBits = case NumBits of
+		  1 -> [{put_bits,1,1,[1]}];
+		  _ -> [{put_bits,Bitmap,NumBits,[1]}]
+	      end,
+    BitmapExpr = extensions_bitmap(Vars, Undefined),
+    B++[{assign,Bitmap,BitmapExpr},
+	{list,[{'cond',[[{eq,Bitmap,0}],
+			['_'|Length ++ PutBits]]}],
+	 {var,"Extensions"}}].
+
 per_enc_optional(Val, DefVals) when is_list(DefVals) ->
     Zero = {put_bits,0,1,[1]},
     One = {put_bits,1,1,[1]},
@@ -414,6 +430,13 @@ enc_element(N, Val0) ->
     {[],[Val,Dst]} = mk_vars(Val0, [element]),
     {[{call,erlang,element,[N,Val],Dst}],Dst}.
 
+enc_maps_get(N, Val0) ->
+    {[],[Val,Dst0]} = mk_vars(Val0, [element]),
+    {var,Dst} = Dst0,
+    DstExpr = {expr,lists:concat(["#{",N,":=",Dst,"}"])},
+    {var,SrcVar} = Val,
+    {[{assign,DstExpr,SrcVar}],Dst0}.
+
 enc_cg(Imm0, false) ->
     Imm1 = enc_cse(Imm0),
     Imm2 = enc_pre_cg(Imm1),
@@ -1231,6 +1254,20 @@ enc_length(Len, {Lb,Ub}, Aligned) when is_integer(Lb) ->
 enc_length(Len, Sv, _Aligned) when is_integer(Sv) ->
     [{'cond',[[{eq,Len,Sv}]]}].
 
+extensions_bitmap(Vs, Undefined) ->
+    Highest = 1 bsl (length(Vs)-1),
+    Cs = extensions_bitmap_1(Vs, Undefined, Highest),
+    lists:flatten(lists:join(" bor ", Cs)).
+
+extensions_bitmap_1([{var,V}|Vs], Undefined, Power) ->
+    S = ["case ",V," of\n",
+         "  ",Undefined," -> 0;\n"
+         "  _ -> ",integer_to_list(Power),"\n"
+         "end"],
+    [S|extensions_bitmap_1(Vs, Undefined, Power bsr 1)];
+extensions_bitmap_1([], _, _) ->
+    [].
+
 put_bits_binary(Bin, _Unit, Aligned) when is_binary(Bin) ->
     Sz = byte_size(Bin),
     <<Int:Sz/unit:8>> = Bin,
diff --git a/lib/asn1/src/asn1ct_value.erl b/lib/asn1/src/asn1ct_value.erl
index b3d41dd9f..8bd99d995 100644
--- a/lib/asn1/src/asn1ct_value.erl
+++ b/lib/asn1/src/asn1ct_value.erl
@@ -64,7 +64,11 @@ from_type(M,Typename,Type) when is_record(Type,type) ->
 	    end;
 	{constructed,bif} when Typename == ['EXTERNAL'] ->
 	    Val=from_type_constructed(M,Typename,InnerType,Type),
-	    asn1ct_eval_ext:transform_to_EXTERNAL1994(Val);
+            T = case M:maps() of
+                    false -> transform_to_EXTERNAL1994;
+                    true -> transform_to_EXTERNAL1994_maps
+                end,
+            asn1ct_eval_ext:T(Val);
 	{constructed,bif} ->
 	    from_type_constructed(M,Typename,InnerType,Type)
     end;
@@ -118,11 +122,13 @@ get_sequence(M,Typename,Type) ->
 	    #'SEQUENCE'{components=Cl} -> {'SEQUENCE',Cl};
 	    #'SET'{components=Cl} -> {'SET',to_textual_order(Cl)}
 	end,
-    case get_components(M,Typename,CompList) of
-        [] ->
-            {list_to_atom(asn1ct_gen:list2rname(Typename))};
-        C ->
-            list_to_tuple([list_to_atom(asn1ct_gen:list2rname(Typename))|C])
+    Cs = get_components(M, Typename, CompList),
+    case M:maps() of
+        false ->
+            RecordTag = list_to_atom(asn1ct_gen:list2rname(Typename)),
+            list_to_tuple([RecordTag|[Val || {_,Val} <- Cs]]);
+        true ->
+            maps:from_list(Cs)
     end.
 
 get_components(M,Typename,{Root,Ext}) ->
@@ -130,9 +136,9 @@ get_components(M,Typename,{Root,Ext}) ->
 
 %% Should enhance this *** HERE *** with proper handling of extensions
 
-get_components(M,Typename,[H|T]) ->
-    [from_type(M,Typename,H)|
-    get_components(M,Typename,T)];
+get_components(M, Typename, [H|T]) ->
+    #'ComponentType'{name=Name} = H,
+    [{Name,from_type(M, Typename, H)}|get_components(M, Typename, T)];
 get_components(_,_,[]) ->
     [].
 
diff --git a/lib/asn1/src/asn1rtt_ext.erl b/lib/asn1/src/asn1rtt_ext.erl
index 3bf01823d..161b2db69 100644
--- a/lib/asn1/src/asn1rtt_ext.erl
+++ b/lib/asn1/src/asn1rtt_ext.erl
@@ -19,7 +19,8 @@
 %%
 
 -module(asn1rtt_ext).
--export([transform_to_EXTERNAL1990/1,transform_to_EXTERNAL1994/1]).
+-export([transform_to_EXTERNAL1990/1,transform_to_EXTERNAL1990_maps/1,
+         transform_to_EXTERNAL1994/1,transform_to_EXTERNAL1994_maps/1]).
 
 transform_to_EXTERNAL1990({_,_,_,_}=Val) ->
     transform_to_EXTERNAL1990(tuple_to_list(Val), []);
@@ -51,6 +52,30 @@ transform_to_EXTERNAL1990([Data_value], Acc)
     list_to_tuple(lists:reverse([{'octet-aligned',Data_value}|Acc])).
 
 
+transform_to_EXTERNAL1990_maps(#{identification:=Id,'data-value':=Value}=V) ->
+    M0 = case Id of
+             {syntax,DRef} ->
+                 #{'direct-reference'=>DRef};
+             {'presentation-context-id',IndRef} ->
+                 #{'indirect-reference'=>IndRef};
+             {'context-negotiation',
+              #{'presentation-context-id':=IndRef,
+                'transfer-syntax':=DRef}} ->
+                 #{'direct-reference'=>DRef,
+                   'indirect-reference'=>IndRef}
+         end,
+    M = case V of
+            #{'data-value-descriptor':=Dvd} ->
+                M0#{'data-value-descriptor'=>Dvd};
+            #{} ->
+                M0
+        end,
+    M#{encoding=>{'octet-aligned',Value}};
+transform_to_EXTERNAL1990_maps(#{encoding:=_}=V) ->
+    %% Already in the EXTERNAL 1990 format.
+    V.
+
+
 transform_to_EXTERNAL1994({'EXTERNAL',DRef,IndRef,Data_v_desc,Encoding}=V) ->
     Identification =
 	case {DRef,IndRef} of
@@ -71,3 +96,38 @@ transform_to_EXTERNAL1994({'EXTERNAL',DRef,IndRef,Data_v_desc,Encoding}=V) ->
 	    %% information.
 	    V
     end.
+
+transform_to_EXTERNAL1994_maps(V0) ->
+    Identification =
+        case V0 of
+            #{'direct-reference':=DRef,
+              'indirect-reference':=asn1_NOVALUE} ->
+		{syntax,DRef};
+            #{'direct-reference':=asn1_NOVALUE,
+              'indirect-reference':=IndRef} ->
+		{'presentation-context-id',IndRef};
+            #{'direct-reference':=DRef,
+              'indirect-reference':=IndRef} ->
+		{'context-negotiation',
+                 #{'transfer-syntax'=>DRef,
+                   'presentation-context-id'=>IndRef}}
+	end,
+    case V0 of
+        #{encoding:={'octet-aligned',Val}}
+          when is_list(Val); is_binary(Val) ->
+	    %% Transform to the EXTERNAL 1994 definition.
+            V = #{identification=>Identification,
+                  'data-value'=>Val},
+            case V0 of
+                #{'data-value-descriptor':=asn1_NOVALUE} ->
+                    V;
+                #{'data-value-descriptor':=Dvd} ->
+                    V#{'data-value-descriptor'=>Dvd}
+            end;
+	_  ->
+	    %% Keep the EXTERNAL 1990 definition to avoid losing
+	    %% information.
+	    V = [{K,V} || {K,V} <- maps:to_list(V0),
+                          V =/= asn1_NOVALUE],
+            maps:from_list(V)
+    end.
diff --git a/lib/asn1/test/Makefile b/lib/asn1/test/Makefile
index 40575e8a2..d346bb9e1 100644
--- a/lib/asn1/test/Makefile
+++ b/lib/asn1/test/Makefile
@@ -82,6 +82,7 @@ MODULES= \
 	testInfObjExtract \
 	testParameterizedInfObj \
 	testFragmented \
+	testMaps \
 	testMergeCompile \
 	testMultipleLevels \
 	testDeepTConstr \
diff --git a/lib/asn1/test/asn1_SUITE.erl b/lib/asn1/test/asn1_SUITE.erl
index b6430134a..6769a38b1 100644
--- a/lib/asn1/test/asn1_SUITE.erl
+++ b/lib/asn1/test/asn1_SUITE.erl
@@ -21,6 +21,9 @@
 
 -module(asn1_SUITE).
 
+%% Suppress compilation of an addititional module compiled for maps.
+-define(NO_MAPS_MODULE, asn1_test_lib_no_maps).
+
 -define(only_ber(Func),
     if Rule =:= ber -> Func;
        true -> ok
@@ -102,6 +105,7 @@ groups() ->
        testMultipleLevels,
        testOpt,
        testSeqDefault,
+       testMaps,
        % Uses 'External'
        {group, [], [testExternal,
                     testSeqExtension]},
@@ -176,8 +180,11 @@ groups() ->
 
      {performance, [],
       [testTimer_ber,
+       testTimer_ber_maps,
        testTimer_per,
-       testTimer_uper]}].
+       testTimer_per_maps,
+       testTimer_uper,
+       testTimer_uper_maps]}].
 
 %%------------------------------------------------------------------------------
 %% Init/end
@@ -441,6 +448,16 @@ testDEFAULT(Config, Rule, Opts) ->
     testDef:main(Rule),
     testSeqSetDefaultVal:main(Rule, Opts).
 
+testMaps(Config) ->
+    test(Config, fun testMaps/3,
+         [{ber,[maps,no_ok_wrapper]},
+          {ber,[maps,der,no_ok_wrapper]},
+          {per,[maps,no_ok_wrapper]},
+          {uper,[maps,no_ok_wrapper]}]).
+testMaps(Config, Rule, Opts) ->
+    asn1_test_lib:compile_all(['Maps'], Config, [Rule|Opts]),
+    testMaps:main(Rule).
+
 testOpt(Config) -> test(Config, fun testOpt/3).
 testOpt(Config, Rule, Opts) ->
     asn1_test_lib:compile("Opt", Config, [Rule|Opts]),
@@ -614,12 +631,12 @@ parse(Config) ->
     [asn1_test_lib:compile(M, Config, [abs]) || M <- test_modules()].
 
 per(Config) ->
-    test(Config, fun per/3, [per,uper]).
+    test(Config, fun per/3, [per,uper,{per,[maps]},{uper,[maps]}]).
 per(Config, Rule, Opts) ->
     [module_test(M, Config, Rule, Opts) || M <- per_modules()].
 
 ber_other(Config) ->
-    test(Config, fun ber_other/3, [ber]).
+    test(Config, fun ber_other/3, [ber,{ber,[maps]}]).
 
 ber_other(Config, Rule, Opts) ->
     [module_test(M, Config, Rule, Opts) || M <- ber_modules()].
@@ -628,7 +645,7 @@ der(Config) ->
     asn1_test_lib:compile_all(ber_modules(), Config, [der]).
 
 module_test(M0, Config, Rule, Opts) ->
-    asn1_test_lib:compile(M0, Config, [Rule|Opts]),
+    asn1_test_lib:compile(M0, Config, [Rule,?NO_MAPS_MODULE|Opts]),
     case list_to_atom(M0) of
 	'LDAP' ->
 	    %% Because of the recursive definition of 'Filter' in
@@ -995,7 +1012,9 @@ testS1AP(Config, Rule, Opts) ->
 testRfcs() ->
     [{timetrap,{minutes,90}}].
 
-testRfcs(Config) ->  test(Config, fun testRfcs/3, [{ber,[der]}]).
+testRfcs(Config) ->  test(Config, fun testRfcs/3,
+                          [{ber,[der,?NO_MAPS_MODULE]},
+                           {ber,[der,maps]}]).
 testRfcs(Config, Rule, Opts) ->
     case erlang:system_info(system_architecture) of
 	"sparc-sun-solaris2.10" ->
@@ -1010,7 +1029,8 @@ test_compile_options(Config) ->
     ok = test_compile_options:path(Config),
     ok = test_compile_options:noobj(Config),
     ok = test_compile_options:record_name_prefix(Config),
-    ok = test_compile_options:verbose(Config).
+    ok = test_compile_options:verbose(Config),
+    ok = test_compile_options:maps(Config).
 
 testDoubleEllipses(Config) -> test(Config, fun testDoubleEllipses/3).
 testDoubleEllipses(Config, Rule, Opts) ->
@@ -1069,7 +1089,7 @@ test_x691(Config, Rule, Opts) ->
     ok.
 
 ticket_6143(Config) ->
-    ok = test_compile_options:ticket_6143(Config).
+    asn1_test_lib:compile("AA1", Config, [?NO_MAPS_MODULE]).
 
 testExtensionAdditionGroup(Config) ->
     test(Config, fun testExtensionAdditionGroup/3).
@@ -1157,20 +1177,33 @@ END
     ok = asn1ct:compile(File, [{outdir, PrivDir}]).
 
 
-timer_compile(Config, Rule) ->
-    asn1_test_lib:compile_all(["H235-SECURITY-MESSAGES", "H323-MESSAGES"],
-                              Config, [no_ok_wrapper,Rule]).
+timer_compile(Config, Opts0) ->
+    Files = ["H235-SECURITY-MESSAGES", "H323-MESSAGES"],
+    Opts = [no_ok_wrapper,?NO_MAPS_MODULE|Opts0],
+    asn1_test_lib:compile_all(Files, Config, Opts).
 
 testTimer_ber(Config) ->
-    timer_compile(Config, ber),
+    timer_compile(Config, [ber]),
     testTimer:go().
 
 testTimer_per(Config) ->
-    timer_compile(Config, per),
+    timer_compile(Config, [per]),
     testTimer:go().
 
 testTimer_uper(Config) ->
-    timer_compile(Config, uper),
+    timer_compile(Config, [uper]),
+    testTimer:go().
+
+testTimer_ber_maps(Config) ->
+    timer_compile(Config, [ber,maps]),
+    testTimer:go().
+
+testTimer_per_maps(Config) ->
+    timer_compile(Config, [per,maps]),
+    testTimer:go().
+
+testTimer_uper_maps(Config) ->
+    timer_compile(Config, [uper,maps]),
     testTimer:go().
 
 %% Test of multiple-line comment, OTP-8043
@@ -1179,9 +1212,11 @@ testComment(Config) ->
     asn1_test_lib:roundtrip('Comment', 'Seq', {'Seq',12,true}).
 
 testName2Number(Config) ->
-    N2NOptions = [{n2n,Type} || Type <- ['CauseMisc', 'CauseProtocol',
-                                         'CauseRadioNetwork',
-                                         'CauseTransport','CauseNas']],
+    N2NOptions0 = [{n2n,Type} ||
+                     Type <- ['CauseMisc', 'CauseProtocol',
+                              'CauseRadioNetwork',
+                              'CauseTransport','CauseNas']],
+    N2NOptions = [?NO_MAPS_MODULE|N2NOptions0],
     asn1_test_lib:compile("S1AP-IEs", Config, N2NOptions),
 
     0 = 'S1AP-IEs':name2num_CauseMisc('control-processing-overload'),
@@ -1191,8 +1226,9 @@ testName2Number(Config) ->
     %% Test that n2n option generates name2num and num2name functions supporting
     %% values not within the extension root if the enumeration type has an
     %% extension marker.
-    N2NOptionsExt = [{n2n, 'NoExt'}, {n2n, 'Ext'}, {n2n, 'Ext2'}],
+    N2NOptionsExt = [?NO_MAPS_MODULE,{n2n,'NoExt'},{n2n,'Ext'},{n2n,'Ext2'}],
     asn1_test_lib:compile("EnumN2N", Config, N2NOptionsExt),
+
     %% Previously, name2num and num2name was not generated if the type didn't
     %% have an extension marker:
     0 = 'EnumN2N':name2num_NoExt('blue'),
@@ -1210,9 +1246,11 @@ testName2Number(Config) ->
     ok.
 
 ticket_7407(Config) ->
-    asn1_test_lib:compile("EUTRA-extract-7407", Config, [uper]),
+    Opts = [uper,?NO_MAPS_MODULE],
+    asn1_test_lib:compile("EUTRA-extract-7407", Config, Opts),
     ticket_7407_code(true),
-    asn1_test_lib:compile("EUTRA-extract-7407", Config, [uper,no_final_padding]),
+    asn1_test_lib:compile("EUTRA-extract-7407", Config,
+                          [no_final_padding|Opts]),
     ticket_7407_code(false).
 
 ticket_7407_code(FinalPadding) ->
diff --git a/lib/asn1/test/asn1_SUITE_data/Maps.asn1 b/lib/asn1/test/asn1_SUITE_data/Maps.asn1
new file mode 100644
index 000000000..fd5f373e4
--- /dev/null
+++ b/lib/asn1/test/asn1_SUITE_data/Maps.asn1
@@ -0,0 +1,17 @@
+Maps DEFINITIONS AUTOMATIC TAGS ::=
+BEGIN
+
+XY ::= SEQUENCE { x INTEGER DEFAULT 0, y INTEGER DEFAULT 0 }
+
+xy1 XY ::= { x 42, y 17 }
+xy2 XY ::= { }
+xy3 XY ::= { y 999 }
+
+S ::= SEQUENCE {
+  xy XY DEFAULT { x 100, y 100 },
+  os OCTET STRING OPTIONAL
+}
+
+s1 S ::= {}
+
+END
diff --git a/lib/asn1/test/asn1_test_lib.erl b/lib/asn1/test/asn1_test_lib.erl
index dc614db4f..a79958d22 100644
--- a/lib/asn1/test/asn1_test_lib.erl
+++ b/lib/asn1/test/asn1_test_lib.erl
@@ -25,7 +25,8 @@
 	 hex_to_bin/1,
 	 match_value/2,
 	 parallel/0,
-	 roundtrip/3,roundtrip/4,roundtrip_enc/3,roundtrip_enc/4]).
+	 roundtrip/3,roundtrip/4,roundtrip_enc/3,roundtrip_enc/4,
+         map_roundtrip/3]).
 
 -include_lib("common_test/include/ct.hrl").
 
@@ -94,15 +95,58 @@ module(F0) ->
     list_to_atom(F).
 %%    filename:join(CaseDir, F ++ ".beam").
 
-compile_file(File, Options) ->
+compile_file(File, Options0) ->
+    Options = [warnings_as_errors|Options0],
     try
-        ok = asn1ct:compile(File, [warnings_as_errors|Options])
+        ok = asn1ct:compile(File, Options),
+        ok = compile_maps(File, Options)
     catch
         _:Reason ->
 	    ct:print("Failed to compile ~s\n~p", [File,Reason]),
             error
     end.
 
+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],
+    case lists:any(fun(E) -> lists:member(E, Incompat) end, Options) of
+        true ->
+            ok;
+        false ->
+            compile_maps_1(File, Options)
+    end.
+
+compile_maps_1(File, Options) ->
+    ok = asn1ct:compile(File, [maps,no_ok_wrapper,noobj|Options]),
+    OutDir = proplists:get_value(outdir, Options),
+    Base0 = filename:rootname(filename:basename(File)),
+    Base = case filename:extension(Base0) of
+               ".set" ->
+                   filename:rootname(Base0);
+               _ ->
+                   Base0
+           end,
+    ErlBase = Base ++ ".erl",
+    ErlFile = filename:join(OutDir, ErlBase),
+    {ok,Erl0} = file:read_file(ErlFile),
+    Erl = re:replace(Erl0, <<"-module\\('">>, "&maps_"),
+    MapsErlFile = filename:join(OutDir, "maps_" ++ ErlBase),
+    ok = file:write_file(MapsErlFile, Erl),
+    {ok,_} = compile:file(MapsErlFile, [report,{outdir,OutDir},{i,OutDir}]),
+    ok.
+
+unload_map_mod(File0) ->
+    File1 = filename:basename(File0),
+    File2 = filename:rootname(File1, ".asn"),
+    File3 = filename:rootname(File2, ".asn1"),
+    File4 = filename:rootname(File3, ".py"),
+    File = filename:rootname(File4, ".set"),
+    MapMod = list_to_atom("maps_"++File),
+    code:delete(MapMod),
+    code:purge(MapMod),
+    ok.
+
 compile_erlang(Mod, Config, Options) ->
     DataDir = proplists:get_value(data_dir, Config),
     CaseDir = proplists:get_value(case_dir, Config),
@@ -147,24 +191,60 @@ roundtrip(Mod, Type, Value) ->
     roundtrip(Mod, Type, Value, Value).
 
 roundtrip(Mod, Type, Value, ExpectedValue) ->
-    {ok,Encoded} = Mod:encode(Type, Value),
-    {ok,ExpectedValue} = Mod:decode(Type, Encoded),
-    test_ber_indefinite(Mod, Type, Encoded, ExpectedValue),
-    ok.
+    roundtrip_enc(Mod, Type, Value, ExpectedValue).
 
 roundtrip_enc(Mod, Type, Value) ->
     roundtrip_enc(Mod, Type, Value, Value).
 
 roundtrip_enc(Mod, Type, Value, ExpectedValue) ->
-    {ok,Encoded} = Mod:encode(Type, Value),
-    {ok,ExpectedValue} = Mod:decode(Type, Encoded),
+    case Mod:encode(Type, Value) of
+        {ok,Encoded} ->
+            {ok,ExpectedValue} = Mod:decode(Type, Encoded);
+        Encoded when is_binary(Encoded) ->
+            ExpectedValue = Mod:decode(Type, Encoded)
+    end,
+    map_roundtrip(Mod, Type, Encoded),
     test_ber_indefinite(Mod, Type, Encoded, ExpectedValue),
     Encoded.
 
+map_roundtrip(Mod, Type, Encoded) ->
+    MapMod = list_to_atom("maps_"++atom_to_list(Mod)),
+    try MapMod:maps() of
+        true ->
+            map_roundtrip_1(MapMod, Type, Encoded)
+    catch
+        error:undef ->
+            ok
+    end.
+
 %%%
 %%% Internal functions.
 %%%
 
+map_roundtrip_1(Mod, Type, Encoded) ->
+    Decoded = Mod:decode(Type, Encoded),
+    case Mod:encode(Type, Decoded) of
+        Encoded ->
+            ok;
+        OtherEncoding ->
+            case is_named_bitstring(Decoded) of
+                true ->
+                    %% In BER, named BIT STRINGs with different number of
+                    %% trailing zeroes decode to the same value.
+                    ok;
+                false ->
+                    error({encode_mismatch,Decoded,Encoded,OtherEncoding})
+            end
+    end,
+    ok.
+
+is_named_bitstring([H|T]) ->
+    is_atom(H) andalso is_named_bitstring(T);
+is_named_bitstring([]) ->
+    true;
+is_named_bitstring(_) ->
+    false.
+
 hex2num(C) when $0 =< C, C =< $9 -> C - $0;
 hex2num(C) when $A =< C, C =< $F -> C - $A + 10;
 hex2num(C) when $a =< C, C =< $f -> C - $a + 10.
@@ -179,7 +259,12 @@ test_ber_indefinite(Mod, Type, Encoded, ExpectedValue) ->
     case Mod:encoding_rule() of
 	ber ->
 	    Indefinite = iolist_to_binary(ber_indefinite(Encoded)),
-	    {ok,ExpectedValue} = Mod:decode(Type, Indefinite);
+            case Mod:decode(Type, Indefinite) of
+                {ok,ExpectedValue} ->
+                    ok;
+                ExpectedValue ->
+                    ok
+            end;
 	_ ->
 	    ok
     end.
diff --git a/lib/asn1/test/testContextSwitchingTypes.erl b/lib/asn1/test/testContextSwitchingTypes.erl
index 10012908a..5688d8afd 100644
--- a/lib/asn1/test/testContextSwitchingTypes.erl
+++ b/lib/asn1/test/testContextSwitchingTypes.erl
@@ -90,5 +90,6 @@ check_object_identifier(Tuple) when is_tuple(Tuple) ->
 enc_dec(T, V0) ->
     M = 'ContextSwitchingTypes',
     {ok,Enc} = M:encode(T, V0),
+    asn1_test_lib:map_roundtrip(M, T, Enc),
     {ok,V} = M:decode(T, Enc),
     V.
diff --git a/lib/asn1/test/testInfObj.erl b/lib/asn1/test/testInfObj.erl
index 5a9f47d86..c519c70cd 100644
--- a/lib/asn1/test/testInfObj.erl
+++ b/lib/asn1/test/testInfObj.erl
@@ -197,5 +197,6 @@ roundtrip(M, T, V) ->
 
 enc_dec(M, T, V0) ->
     {ok,Enc} = M:encode(T, V0),
+    asn1_test_lib:map_roundtrip(M, T, Enc),
     {ok,V} = M:decode(T, Enc),
     V.
diff --git a/lib/asn1/test/testMaps.erl b/lib/asn1/test/testMaps.erl
new file mode 100644
index 000000000..45dd2255b
--- /dev/null
+++ b/lib/asn1/test/testMaps.erl
@@ -0,0 +1,50 @@
+%%
+%% %CopyrightBegin%
+%%
+%% Copyright Ericsson AB 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(testMaps).
+
+-export([main/1]).
+
+main(_) ->
+    M = 'Maps',
+    true = M:maps(),
+
+    true = M:xy1() =:= #{x=>42,y=>17},
+    true = M:xy2() =:= #{x=>0,y=>0},
+    true = M:xy3() =:= #{x=>0,y=>999},
+    true = M:s1() =:= #{xy=>#{x=>100,y=>100}},
+
+    roundtrip('XY', M:xy1()),
+    roundtrip('XY', M:xy2()),
+    roundtrip('XY', M:xy3()),
+    roundtrip('XY', #{}, #{x=>0,y=>0}),
+
+    roundtrip('S', M:s1()),
+    roundtrip('S', #{}, #{xy=>#{x=>100,y=>100}}),
+    roundtrip('S', #{os=><<1,2,3>>}, #{xy=>#{x=>100,y=>100},
+                                       os=><<1,2,3>>}),
+
+    ok.
+
+roundtrip(Type, Value) ->
+    roundtrip(Type, Value, Value).
+
+roundtrip(Type, Value, Expected) ->
+    asn1_test_lib:roundtrip('Maps', Type, Value, Expected).
diff --git a/lib/asn1/test/testRfcs.erl b/lib/asn1/test/testRfcs.erl
index da7333ef9..20176e35e 100644
--- a/lib/asn1/test/testRfcs.erl
+++ b/lib/asn1/test/testRfcs.erl
@@ -35,22 +35,27 @@ compile(Config, Erules, Options0) ->
     asn1_test_lib:compile_all(Specs, Config, [Erules,{i,CaseDir}|Options]).
 
 test() ->
-    {1,3,6,1,5,5,7,48,1,2} =
-	IdPkixOcspNonce =
-	'OCSP-2009':'id-pkix-ocsp-nonce'(),
-    roundtrip('OCSP-2009', 'OCSPRequest',
-	      {'OCSPRequest',
-	       {'TBSRequest',
-		0,
-		{rfc822Name,"name string"},
-		[{'Request',
-		  {'CertID',{'_',{2,9,3,4,5},asn1_NOVALUE},
-		   <<"POTATOHASH">>,<<"HASHBROWN">>,42},
-		  [{'_',IdPkixOcspNonce,true,<<34,159,16,57,199>>}]}],
-		asn1_NOVALUE},
-	       asn1_NOVALUE}),
-    otp_7759(),
-    ok.
+    M = 'OCSP-2009',
+    case M:maps() of
+        false ->
+            {1,3,6,1,5,5,7,48,1,2} =
+                IdPkixOcspNonce =
+                'OCSP-2009':'id-pkix-ocsp-nonce'(),
+            roundtrip('OCSP-2009', 'OCSPRequest',
+                      {'OCSPRequest',
+                       {'TBSRequest',
+                        0,
+                        {rfc822Name,"name string"},
+                        [{'Request',
+                          {'CertID',{'_',{2,9,3,4,5},asn1_NOVALUE},
+                           <<"POTATOHASH">>,<<"HASHBROWN">>,42},
+                          [{'_',IdPkixOcspNonce,true,<<34,159,16,57,199>>}]}],
+                        asn1_NOVALUE},
+                       asn1_NOVALUE}),
+            otp_7759(records);
+        true ->
+            otp_7759(maps)
+    end.
 
 roundtrip(Module, Type, Value0) ->
     Enc = Module:encode(Type, Value0),
@@ -58,7 +63,7 @@ roundtrip(Module, Type, Value0) ->
     asn1_test_lib:match_value(Value0, Value1),
     ok.
 
-otp_7759() ->
+otp_7759(Pack) ->
     %% The release note for asn-1.6.6 says:
     %%   Decode of an open_type when the value was empty tagged
     %%   type encoded with indefinite length failed.
@@ -66,10 +71,15 @@ otp_7759() ->
     Encoded = encoded_msg(),
     ContentInfo = Mod:decode('ContentInfo', Encoded),
     io:format("~p\n", [ContentInfo]),
-    {'ContentInfo',_Id,PKCS7_content} = ContentInfo,
-    X = Mod:decode('SignedData', PKCS7_content),
+    Content = case ContentInfo of
+                  {'ContentInfo',_Id,Content0} when Pack =:= records ->
+                      Content0;
+                  #{'content-type':=_,'pkcs7-content':=Content0}
+                    when Pack =:= maps ->
+                      Content0
+              end,
+    X = Mod:decode('SignedData', Content),
     io:format("~p\n", [X]),
-    io:nl(),
     ok.
 
 encoded_msg() ->
diff --git a/lib/asn1/test/testTCAP.erl b/lib/asn1/test/testTCAP.erl
index 422ae1f0f..a6f0f9fad 100644
--- a/lib/asn1/test/testTCAP.erl
+++ b/lib/asn1/test/testTCAP.erl
@@ -92,5 +92,6 @@ test_asn1config() ->
 enc_dec(T, V0) ->
     M = 'TCAPPackage',
     {ok,Enc} = M:encode(T, V0),
+    asn1_test_lib:map_roundtrip(M, T, Enc),
     {ok,V} = M:decode(T, Enc),
     V.
diff --git a/lib/asn1/test/testTimer.erl b/lib/asn1/test/testTimer.erl
index bd8da8573..3edeb1b71 100644
--- a/lib/asn1/test/testTimer.erl
+++ b/lib/asn1/test/testTimer.erl
@@ -25,7 +25,42 @@
 
 -define(times, 5000).
 
-val() ->
+go() ->
+    Module = 'H323-MESSAGES',
+    Type = 'H323-UserInformation',
+    Value = case Module:maps() of
+                false -> val_records();
+                true -> val_maps()
+            end,
+    Bytes = Module:encode(Type, Value),
+    Value = Module:decode(Type, Bytes),
+
+    {ValWr,done} = timer:tc(fun() -> encode(?times, Module, Type, Value) end),
+    io:format("ASN.1 encoding: ~p micro~n", [ValWr / ?times]),
+
+    done = decode(2, Module, Type, Bytes),
+
+    {ValRead,done} = timer:tc(fun() -> decode(?times, Module, Type, Bytes) end),
+    io:format("ASN.1 decoding: ~p micro~n", [ValRead /?times]),
+
+    Comment = "encode: "++integer_to_list(round(ValWr/?times)) ++
+	" micro, decode: "++integer_to_list(round(ValRead /?times)) ++
+	" micro. [" ++ atom_to_list(Module:encoding_rule()) ++ "]",
+    {comment,Comment}.
+
+encode(0, _Module,_Type,_Value) ->
+    done;
+encode(N, Module,Type,Value) ->
+    Module:encode(Type, Value),
+    encode(N-1, Module, Type, Value).
+
+decode(0, _Module, _Type, _Value) ->
+    done;
+decode(N, Module, Type, Value) ->
+    Module:decode(Type, Value),
+    decode(N-1, Module, Type, Value).
+
+val_records() ->
     {'H323-UserInformation',{'H323-UU-PDU',
 			     {callProceeding,
 			      {'CallProceeding-UUIE',
@@ -126,34 +161,66 @@ val() ->
      {'H323-UserInformation_user-data',24,<<"O">>}}.
     
 
-go() ->
-    Module = 'H323-MESSAGES',
-    Type = 'H323-UserInformation',
-    Value = val(),
-    Bytes = Module:encode(Type, Value),
-    Value = Module:decode(Type, Bytes),
-
-    {ValWr,done} = timer:tc(fun() -> encode(?times, Module, Type, Value) end),
-    io:format("ASN.1 encoding: ~p micro~n", [ValWr / ?times]),
-
-    done = decode(2, Module, Type, Bytes),
-
-    {ValRead,done} = timer:tc(fun() -> decode(?times, Module, Type, Bytes) end),
-    io:format("ASN.1 decoding: ~p micro~n", [ValRead /?times]),
-
-    Comment = "encode: "++integer_to_list(round(ValWr/?times)) ++
-	" micro, decode: "++integer_to_list(round(ValRead /?times)) ++
-	" micro. [" ++ atom_to_list(Module:encoding_rule()) ++ "]",
-    {comment,Comment}.
-
-encode(0, _Module,_Type,_Value) ->
-    done;
-encode(N, Module,Type,Value) ->
-    Module:encode(Type, Value),
-    encode(N-1, Module, Type, Value).
-
-decode(0, _Module, _Type, _Value) ->
-    done;
-decode(N, Module, Type, Value) ->
-    Module:decode(Type, Value),
-    decode(N-1, Module, Type, Value).
+val_maps() ->
+#{'h323-uu-pdu' => #{h245Control => [],
+                     h245Tunneling => true,
+    'h323-message-body' => {callProceeding,#{callIdentifier => #{guid => <<"OCTET STRINGOCTE">>},
+                      cryptoTokens => [{cryptoGKPwdEncr,#{algorithmOID => {1,18,467,467},
+                                          encryptedData => <<"OC">>,
+                                          paramS => #{iv8 => <<"OCTET ST">>,
+                                            ranInt => -7477016}}},
+                       {cryptoGKPwdEncr,#{algorithmOID => {1,19,486,486},
+                                          encryptedData => <<>>,
+                                          paramS => #{iv8 => <<"OCTET ST">>,
+                                            ranInt => -2404513}}}],
+                      destinationInfo => #{gatekeeper => #{nonStandardData => #{data => <<"O">>,
+                            nonStandardIdentifier => {object,{0,10,260}}}},
+                        gateway => #{nonStandardData => #{data => <<"O">>,
+                            nonStandardIdentifier => {object,{0,13,326}}},
+                          protocol => [{h320,#{dataRatesSupported => [#{channelMultiplier => 78,
+                                      channelRate => 1290470518,
+                                      nonStandardData => #{data => <<"O">>,
+                                        nonStandardIdentifier => {object,{0,11,295}}}}],
+                                   nonStandardData => #{data => <<"O">>,
+                                     nonStandardIdentifier => {object,{0,11,282}}},
+                                   supportedPrefixes => [#{nonStandardData => #{data => <<"O">>,
+                                        nonStandardIdentifier => {object,{0,12,312}}},
+                                      prefix => {'h323-ID',"BM"}}]}}]},
+                        mc => true,
+                        mcu => #{nonStandardData => #{data => <<"OC">>,
+                            nonStandardIdentifier => {object,{1,13,340,340}}}},
+                        nonStandardData => #{data => <<"O">>,nonStandardIdentifier => {object,{0,9,237}}},
+                        terminal => #{nonStandardData => #{data => <<"OC">>,
+                            nonStandardIdentifier => {object,{1,14,353,354}}}},
+                        undefinedNode => true,
+                        vendor => #{productId => <<"OC">>,
+                          vendor => #{manufacturerCode => 16282,
+                            t35CountryCode => 62,
+                            t35Extension => 63},
+                          versionId => <<"OC">>}},
+                      fastStart => [],
+                      h245Address => {ipxAddress,#{netnum => <<"OCTE">>,
+                                    node => <<"OCTET ">>,
+                                    port => <<"OC">>}},
+                      h245SecurityMode => {noSecurity,'NULL'},
+                      protocolIdentifier => {0,8,222},
+                      tokens => [#{certificate => #{certificate => <<"OC">>,type => {1,16,405,406}},
+                         challenge => <<"OCTET STR">>,
+                         dhkey => #{generator => <<1:1>>,halfkey => <<1:1>>,modSize => <<1:1>>},
+                         generalID => "BMP",
+                         nonStandard => #{data => <<"OC">>,nonStandardIdentifier => {1,16,414,415}},
+                         password => "BM",
+                         random => -26430296,
+                         timeStamp => 1667517741},
+                       #{certificate => #{certificate => <<"OC">>,type => {1,17,442,443}},
+                         challenge => <<"OCTET STRI">>,
+                         dhkey => #{generator => <<1:1>>,halfkey => <<1:1>>,modSize => <<1:1>>},
+                         generalID => "BMP",
+                         nonStandard => #{data => <<"OC">>,nonStandardIdentifier => {1,18,452,452}},
+                         password => "BMP",
+                         random => -16356110,
+                         timeStamp => 1817656756}]}},
+    h4501SupplementaryService => [],
+    nonStandardControl => [],
+    nonStandardData => #{data => <<>>,nonStandardIdentifier => {object,{0,3,84}}}},
+  'user-data' => #{'protocol-discriminator' => 24,'user-information' => <<"O">>}}.
diff --git a/lib/asn1/test/testUniqueObjectSets.erl b/lib/asn1/test/testUniqueObjectSets.erl
index 4d3ec9439..30cbceb57 100644
--- a/lib/asn1/test/testUniqueObjectSets.erl
+++ b/lib/asn1/test/testUniqueObjectSets.erl
@@ -27,6 +27,7 @@ seq_roundtrip(I, D0) ->
     M = 'UniqueObjectSets',
     try
 	{ok,Enc} = M:encode('Seq', {'Seq',I,D0}),
+        asn1_test_lib:map_roundtrip(M, 'Seq', Enc),
 	{ok,{'Seq',I,D}} = M:decode('Seq', Enc),
 	D
     catch C:E ->
diff --git a/lib/asn1/test/test_compile_options.erl b/lib/asn1/test/test_compile_options.erl
index ac7447053..c15e61550 100644
--- a/lib/asn1/test/test_compile_options.erl
+++ b/lib/asn1/test/test_compile_options.erl
@@ -24,8 +24,8 @@
 -include_lib("common_test/include/ct.hrl").
 
 
--export([wrong_path/1,comp/2,path/1,ticket_6143/1,noobj/1,
-	 record_name_prefix/1,verbose/1]).
+-export([wrong_path/1,comp/2,path/1,noobj/1,
+	 record_name_prefix/1,verbose/1,maps/1]).
 
 %% OTP-5689
 wrong_path(Config) ->
@@ -64,8 +64,6 @@ path(Config) ->
     file:set_cwd(CWD),
     ok.
 
-ticket_6143(Config) -> asn1_test_lib:compile("AA1", Config, []).
-
 noobj(Config) ->
     DataDir = proplists:get_value(data_dir,Config),
     OutDir = proplists:get_value(priv_dir,Config),
@@ -130,6 +128,28 @@ verbose(Config) when is_list(Config) ->
     [] = test_server:capture_get(),
     ok.
 
+maps(Config) ->
+    DataDir = proplists:get_value(data_dir, Config),
+    OutDir = proplists:get_value(case_dir, Config),
+    InFile = filename:join(DataDir, "P-Record"),
+
+    do_maps(ber, InFile, OutDir),
+    do_maps(per, InFile, OutDir),
+    do_maps(uper, InFile, OutDir).
+
+do_maps(Erule, InFile, OutDir) ->
+    Opts = [Erule,maps,{outdir,OutDir}],
+    ok = asn1ct:compile(InFile, Opts),
+
+    %% Make sure that no .hrl files are generated.
+    [] = filelib:wildcard(filename:join(OutDir, "*.hrl")),
+
+    %% Remove all generated files.
+    All = filelib:wildcard(filename:join(OutDir, "*")),
+    _ = [file:delete(N) || N <- All],
+
+    ok.
+
 outfiles_check(OutDir) ->
     outfiles_check(OutDir,outfiles1()).
 
-- 
2.11.1

openSUSE Build Service is sponsored by