File 2400-asn1-Remove-deprecated-functions.patch of Package erlang

From c82bbd8f28f3e0ce00f5db44f7a6cef75653eee5 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Thu, 10 Sep 2015 16:10:31 +0200
Subject: [PATCH] asn1: Remove deprecated functions

Remove the entire asn1rt module. All functions in it were deprecated in
OTP 17.

In asn1ct, remove the deprecated functions asn1ct:encode/3 and
asn1ct:decode/3. Also remove asn1ct:encode/2, which has not been
formally deprecated but is undocumented.
---
 lib/asn1/doc/src/Makefile                          |   3 +-
 lib/asn1/doc/src/asn1ct.xml                        |  45 +----
 lib/asn1/doc/src/asn1rt.xml                        | 135 ---------------
 lib/asn1/src/Makefile                              |   1 -
 lib/asn1/src/asn1.app.src                          |   1 -
 lib/asn1/src/asn1ct.erl                            |  24 +--
 lib/asn1/src/asn1ct_value.erl                      |   7 +-
 lib/asn1/src/asn1rt.erl                            | 184 ---------------------
 .../asn1_SUITE_data/extensionAdditionGroup.erl     |   4 +-
 lib/asn1/test/asn1_SUITE_data/testobj.erl          |  10 +-
 lib/asn1/test/testPrimStrings.erl                  |  22 +--
 lib/stdlib/src/otp_internal.erl                    |  20 ++-
 12 files changed, 38 insertions(+), 418 deletions(-)
 delete mode 100644 lib/asn1/doc/src/asn1rt.xml
 delete mode 100644 lib/asn1/src/asn1rt.erl

diff --git a/lib/asn1/doc/src/Makefile b/lib/asn1/doc/src/Makefile
index 559836116..9a388e4e8 100644
--- a/lib/asn1/doc/src/Makefile
+++ b/lib/asn1/doc/src/Makefile
@@ -37,8 +37,7 @@ RELSYSDIR = $(RELEASE_PATH)/lib/$(APPLICATION)-$(VSN)
 # Target Specs
 # ----------------------------------------------------
 XML_APPLICATION_FILES = ref_man.xml
-XML_REF3_FILES = asn1ct.xml \
-	asn1rt.xml
+XML_REF3_FILES = asn1ct.xml
 
 GEN_XML = \
 	asn1_spec.xml
diff --git a/lib/asn1/doc/src/asn1ct.xml b/lib/asn1/doc/src/asn1ct.xml
index e5a7b1bcc..ebe1ce44d 100644
--- a/lib/asn1/doc/src/asn1ct.xml
+++ b/lib/asn1/doc/src/asn1ct.xml
@@ -321,45 +321,6 @@ File3.asn</pre>
     </func>
 
     <func>
-      <name>encode(Module, Type, Value)-> {ok, Bytes} | {error, Reason}</name>
-      <fsummary>Encodes an ASN.1 value.</fsummary>
-      <type>
-        <v>Module = Type = atom()</v>
-        <v>Value = term()</v>
-        <v>Bytes = binary()</v>
-        <v>Reason = term()</v>
-      </type>
-      <desc>
-        <p>Encodes <c>Value</c> of <c>Type</c> defined in the <c>ASN.1</c> module
-          <c>Module</c>. To get as fast execution as possible, the
-          encode function performs only the rudimentary tests that input 
-          <c>Value</c> is a correct instance of <c>Type</c>. So, for example,
-	  the length of strings is
-          not always checked. Returns <c>{ok, Bytes}</c> if successful or
-          <c>{error, Reason}</c> if an error occurred.
-          </p>
-	<p>This function is deprecated.
-	Use <c>Module:encode(Type, Value)</c> instead.</p>
-      </desc>
-    </func>
-
-    <func>
-      <name>decode(Module, Type, Bytes) -> {ok, Value} | {error, Reason}</name>
-      <fsummary>Decode from Bytes into an ASN.1 value.</fsummary>
-      <type>
-        <v>Module = Type = atom()</v>
-        <v>Value = Reason = term()</v>
-        <v>Bytes = binary()</v>
-      </type>
-      <desc>
-        <p>Decodes <c>Type</c> from <c>Module</c> from the binary
-          <c>Bytes</c>. Returns <c>{ok, Value}</c> if successful.</p>
-	<p>This function is deprecated.
-	Use <c>Module:decode(Type, Bytes)</c> instead.</p>
-      </desc>
-    </func>
-
-    <func>
       <name>value(Module, Type) -> {ok, Value} | {error, Reason}</name>
       <fsummary>Creates an ASN.1 value for test purposes.</fsummary>
       <type>
@@ -424,11 +385,11 @@ File3.asn</pre>
         <p>Schematically, the following occurs for each type in the module:</p>
         <code type="none">
 {ok, Value} = asn1ct:value(Module, Type),
-{ok, Bytes} = asn1ct:encode(Module, Type, Value),
-{ok, Value} = asn1ct:decode(Module, Type, Bytes).</code>
+{ok, Bytes} = Module:encode(Type, Value),
+{ok, Value} = Module:decode(Type, Bytes).</code>
         <p>The <c>test</c> functions use the <c>*.asn1db</c> files
           for all included modules. If they are located in a different
-          directory than the current working directory, use the include
+          directory than the current working directory, use the <c>include</c>
           option to add paths. This is only needed when automatically
           generating values. For static values using <c>Value</c> no
           options are needed.</p>
diff --git a/lib/asn1/doc/src/asn1rt.xml b/lib/asn1/doc/src/asn1rt.xml
deleted file mode 100644
index 3f53ca0f5..000000000
--- a/lib/asn1/doc/src/asn1rt.xml
+++ /dev/null
@@ -1,135 +0,0 @@
-<?xml version="1.0" encoding="utf-8" ?>
-<!DOCTYPE erlref SYSTEM "erlref.dtd">
-
-<erlref>
-  <header>
-    <copyright>
-      <year>1997</year><year>2016</year>
-      <holder>Ericsson AB. All Rights Reserved.</holder>
-    </copyright>
-    <legalnotice>
-      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.
-    
-    </legalnotice>
-
-    <title>asn1rt</title>
-    <prepared>Kenneth Lundin</prepared>
-    <responsible>Kenneth Lundin</responsible>
-    <docno>1</docno>
-    <approved>Kenneth Lundin</approved>
-    <checked></checked>
-    <date>97-10-04</date>
-    <rev>A</rev>
-    <file>asn1.sgml</file>
-  </header>
-  <module>asn1rt</module>
-  <modulesummary>ASN.1 runtime support functions</modulesummary>
-  <description>
-    <warning>
-      <p>
-	All functions in this module are deprecated and will be
-	removed in a future release.
-      </p>
-    </warning>
-  </description>
-
-  <funcs>
-
-    <func>
-      <name>decode(Module,Type,Bytes) -> {ok,Value}|{error,Reason}</name>
-      <fsummary>Decodes from Bytes into an ASN.1 value.</fsummary>
-      <type>
-        <v>Module = Type = atom()</v>
-        <v>Value = Reason = term()</v>
-        <v>Bytes = binary</v>
-      </type>
-      <desc>
-        <p>Decodes <c>Type</c> from <c>Module</c> from the binary <c>Bytes</c>.
-          Returns <c>{ok,Value}</c> if successful.</p>
-	<p>Use <c>Module:decode(Type, Bytes)</c> instead of this function.</p>
-      </desc>
-    </func>
-
-    <func>
-      <name>encode(Module,Type,Value)-> {ok,Bytes} | {error,Reason}</name>
-      <fsummary>Encodes an ASN.1 value.</fsummary>
-      <type>
-        <v>Module = Type = atom()</v>
-        <v>Value = term()</v>
-        <v>Bytes = binary</v>
-        <v>Reason = term()</v>
-      </type>
-      <desc>
-        <p>Encodes <c>Value</c> of <c>Type</c> defined in the <c>ASN.1</c>
-        module <c>Module</c>. Returns a binary if successful. To get
-        as fast execution as possible, the encode function performs
-        only the rudimentary test that input <c>Value</c> is a correct
-        instance of <c>Type</c>. For example, the length of strings is
-        not always checked.</p>
-	<p>Use <c>Module:encode(Type, Value)</c> instead of this function.</p>
-      </desc>
-    </func>
-
-    <func>
-      <name>info(Module) ->  {ok,Info} | {error,Reason}</name>
-      <fsummary>Returns compiler information about the Module.</fsummary>
-      <type>
-        <v>Module = atom()</v>
-        <v>Info = list()</v>
-        <v>Reason = term()</v>
-      </type>
-      <desc>
-        <p>Returns the version of the <c>ASN.1</c> compiler that was
-          used to compile the module. It also returns the compiler options
-          that were used.</p>
-	<p>Use <c>Module:info()</c> instead of this function.</p>
-      </desc>
-    </func>
-
-    <func>
-      <name>utf8_binary_to_list(UTF8Binary) ->  {ok,UnicodeList} | {error,Reason}</name>
-      <fsummary>Transforms an UTF8 encoded binary to a unicode list.</fsummary>
-      <type>
-        <v>UTF8Binary = binary()</v>
-        <v>UnicodeList = [integer()]</v>
-        <v>Reason = term()</v>
-      </type>
-      <desc>
-        <p>Transforms a UTF8 encoded binary
-          to a list of integers, where each integer represents one
-          character as its unicode value. The function fails if the binary
-          is not a properly encoded UTF8 string.</p>
-	<p>Use <seealso marker="stdlib:unicode#characters_to_list-1">unicode:characters_to_list/1</seealso> instead of this function.</p>
-      </desc>
-    </func>
-
-    <func>
-      <name>utf8_list_to_binary(UnicodeList) ->  {ok,UTF8Binary} | {error,Reason}</name>
-      <fsummary>Transforms an unicode list to a UTF8 binary.</fsummary>
-      <type>
-        <v>UnicodeList = [integer()]</v>
-        <v>UTF8Binary = binary()</v>
-        <v>Reason = term()</v>
-      </type>
-      <desc>
-        <p>Transforms a list of integers,
-          where each integer represents one character as its unicode
-          value, to a UTF8 encoded binary.</p>
-	<p>Use <seealso marker="stdlib:unicode#characters_to_binary-1">unicode:characters_to_binary/1</seealso> instead of this function.</p>
-      </desc>
-    </func>
-
-  </funcs>
-
-</erlref>
-
diff --git a/lib/asn1/src/Makefile b/lib/asn1/src/Makefile
index 38cf2d496..ba459f6cd 100644
--- a/lib/asn1/src/Makefile
+++ b/lib/asn1/src/Makefile
@@ -68,7 +68,6 @@ CT_MODULES= \
 	$(EVAL_CT_MODULES)
 
 RT_MODULES= \
-	asn1rt \
 	asn1rt_nif
 
 MODULES= $(CT_MODULES) $(RT_MODULES) 
diff --git a/lib/asn1/src/asn1.app.src b/lib/asn1/src/asn1.app.src
index 1f8805ff5..d2da72719 100644
--- a/lib/asn1/src/asn1.app.src
+++ b/lib/asn1/src/asn1.app.src
@@ -2,7 +2,6 @@
  [{description, "The Erlang ASN1 compiler version %VSN%"},
   {vsn, "%VSN%"},
   {modules, [
-	asn1rt,
         asn1rt_nif
              ]},
   {registered, [
diff --git a/lib/asn1/src/asn1ct.erl b/lib/asn1/src/asn1ct.erl
index 8783b5418..4e030861f 100644
--- a/lib/asn1/src/asn1ct.erl
+++ b/lib/asn1/src/asn1ct.erl
@@ -20,17 +20,12 @@
 %%
 %%
 -module(asn1ct).
--deprecated([decode/3,encode/3]).
--compile([{nowarn_deprecated_function,{asn1rt,decode,3}},
-	  {nowarn_deprecated_function,{asn1rt,encode,2}},
-	  {nowarn_deprecated_function,{asn1rt,encode,3}}]).
 
 %% Compile Time functions for ASN.1 (e.g ASN.1 compiler).
 
 %%-compile(export_all).
 %% Public exports
 -export([compile/1, compile/2]).
--export([encode/2, encode/3, decode/3]).
 -export([test/1, test/2, test/3, value/2, value/3]).
 %% Application internal exports
 -export([compile_asn/3,compile_asn1/3,compile_py/3,compile/3,
@@ -1271,21 +1266,6 @@ pretty2(Module,AbsFile) ->
 start(Includes) when is_list(Includes) ->
     asn1_db:dbstart(Includes).
 
-
-encode(Module,Term) ->
-    asn1rt:encode(Module,Term).
-
-encode(Module,Type,Term) when is_list(Module) ->
-    asn1rt:encode(list_to_atom(Module),Type,Term);
-encode(Module,Type,Term) ->
-    asn1rt:encode(Module,Type,Term).
-
-decode(Module,Type,Bytes) when is_list(Module) ->
-    asn1rt:decode(list_to_atom(Module),Type,Bytes);
-decode(Module,Type,Bytes) ->
-    asn1rt:decode(Module,Type,Bytes).
-
-
 test(Module)                             -> test_module(Module, []).
 
 test(Module, [] = Options)               -> test_module(Module, Options);
@@ -1330,10 +1310,10 @@ test_type(Module, Type) ->
 
 test_value(Module, Type, Value) ->
     in_process(fun() ->
-                   case catch encode(Module, Type, Value) of
+                   case catch Module:encode(Type, Value) of
                        {ok, Bytes} ->
                            NewBytes = prepare_bytes(Bytes),
-                           case decode(Module, Type, NewBytes) of
+                           case Module:decode(Type, NewBytes) of
                                {ok, Value} ->
                                    {ok, {Module, Type, Value}};
                                {ok, Res}   ->
diff --git a/lib/asn1/src/asn1ct_value.erl b/lib/asn1/src/asn1ct_value.erl
index 57cd3f8af..b3d41dd9f 100644
--- a/lib/asn1/src/asn1ct_value.erl
+++ b/lib/asn1/src/asn1ct_value.erl
@@ -19,7 +19,6 @@
 %%
 %%
 -module(asn1ct_value).
--compile([{nowarn_deprecated_function,{asn1rt,utf8_list_to_binary,1}}]).
 
 %%  Generate Erlang values for ASN.1 types.
 %%  The value is randomized within it's constraints
@@ -292,8 +291,10 @@ from_type_prim(M, D) ->
 	'BMPString' ->
 	    adjust_list(size_random(C),c_string(C,"BMPString"));
 	'UTF8String' ->
-	    {ok,Res}=asn1rt:utf8_list_to_binary(adjust_list(random(50),[$U,$T,$F,$8,$S,$t,$r,$i,$n,$g,16#ffff,16#fffffff,16#ffffff,16#fffff,16#fff])),
-	    Res;
+            L = adjust_list(random(50),
+                            [$U,$T,$F,$8,$S,$t,$r,$i,$n,$g,
+                             16#ffff,16#ffee,16#10ffff,16#ffff,16#fff]),
+	    unicode:characters_to_binary(L);
 	'UniversalString' ->
 	    adjust_list(size_random(C),c_string(C,"UniversalString"));
 	XX ->
diff --git a/lib/asn1/src/asn1rt.erl b/lib/asn1/src/asn1rt.erl
deleted file mode 100644
index 3e09ce225..000000000
--- a/lib/asn1/src/asn1rt.erl
+++ /dev/null
@@ -1,184 +0,0 @@
-%%
-%% %CopyrightBegin%
-%% 
-%% Copyright Ericsson AB 1997-2016. 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(asn1rt).
--deprecated(module).
-
-%% Runtime functions for ASN.1 (i.e encode, decode)
-
--export([encode/2,encode/3,decode/3,load_driver/0,unload_driver/0,info/1]).
-
--export([utf8_binary_to_list/1,utf8_list_to_binary/1]).
-
-encode(Module,{Type,Term}) ->
-    encode(Module,Type,Term).
-
-encode(Module,Type,Term) ->
-    case catch apply(Module,encode,[Type,Term]) of
-	{'EXIT',undef} ->
-	    {error,{asn1,{undef,Module,Type}}};
-	Result ->
-	    Result
-    end.
-
-decode(Module,Type,Bytes) ->
-    case catch apply(Module,decode,[Type,Bytes]) of
-	{'EXIT',undef} ->
-	    {error,{asn1,{undef,Module,Type}}};
-	Result ->
-	    Result
-    end.
-
-%% Remove in R16A
-load_driver() ->
-    ok.
-
-unload_driver() ->
-    ok.
-
-info(Module) ->
-    case catch apply(Module,info,[]) of
-	{'EXIT',{undef,_Reason}} ->
-	    {error,{asn1,{undef,Module,info}}};
-	Result ->
-	    {ok,Result}
-    end.
-
-%% utf8_binary_to_list/1 transforms a utf8 encoded binary to a list of
-%% unicode elements, where each element is the unicode integer value
-%% of a utf8 character.
-%% Bin is a utf8 encoded value. The return value is either {ok,Val} or
-%% {error,Reason}. Val is a list of integers, where each integer is a
-%% unicode character value.
-utf8_binary_to_list(Bin) when is_binary(Bin) ->
-    utf8_binary_to_list(Bin,[]).
-
-utf8_binary_to_list(<<>>,Acc) ->
-    {ok,lists:reverse(Acc)};
-utf8_binary_to_list(Bin,Acc) ->
-    Len = utf8_binary_len(Bin),
-    case catch split_binary(Bin,Len) of
-	{CharBin,RestBin} -> 
-	    case utf8_binary_char(CharBin) of
-		C when is_integer(C) -> 
-		    utf8_binary_to_list(RestBin,[C|Acc]);
-		Err -> Err
-	    end;
-	Err -> {error,{asn1,{bad_encoded_utf8string,Err}}}
-    end.
-	    
-utf8_binary_len(<<0:1,_:7,_/binary>>) ->
-    1;
-utf8_binary_len(<<1:1,1:1,0:1,_:5,_/binary>>) ->
-    2;
-utf8_binary_len(<<1:1,1:1,1:1,0:1,_:4,_/binary>>) ->
-    3;
-utf8_binary_len(<<1:1,1:1,1:1,1:1,0:1,_:3,_/binary>>) ->
-    4;
-utf8_binary_len(<<1:1,1:1,1:1,1:1,1:1,0:1,_:2,_/binary>>) ->
-    5;
-utf8_binary_len(<<1:1,1:1,1:1,1:1,1:1,1:1,0:1,_:1,_/binary>>) ->
-    6;
-utf8_binary_len(Bin) ->
-    {error,{asn1,{bad_utf8_length,Bin}}}.
-
-utf8_binary_char(<<0:1,Int:7>>) ->
-    Int;
-utf8_binary_char(<<_:2,0:1,Int1:5,1:1,0:1,Int2:6>>) ->
-    (Int1 bsl 6) bor Int2;
-utf8_binary_char(<<_:3,0:1,Int1:4,1:1,0:1,Int2:6,1:1,0:1,Int3:6>>) ->
-    <<Res:16>> = <<Int1:4,Int2:6,Int3:6>>,
-    Res;
-utf8_binary_char(<<_:4,0:1,Int1:3,Rest/binary>>) ->
-    <<1:1,0:1,Int2:6,1:1,0:1,Int3:6,1:1,0:1,Int4:6>> = Rest,
-    <<Res:24>> = <<0:3,Int1:3,Int2:6,Int3:6,Int4:6>>,
-    Res;
-utf8_binary_char(<<_:5,0:1,Int1:2,Rest/binary>>) ->
-    <<1:1,0:1,Int2:6,1:1,0:1,Int3:6,1:1,0:1,Int4:6,1:1,0:1,Int5:6>> = Rest,
-    <<Res:32>> = <<0:6,Int1:2,Int2:6,Int3:6,Int4:6,Int5:6>>,
-    Res;
-utf8_binary_char(<<_:6,0:1,I:1,Rest/binary>>) ->
-    <<1:1,0:1,Int2:6,1:1,0:1,Int3:6,1:1,0:1,Int4:6,1:1,0:1,
-     Int5:6,1:1,0:1,Int6:6>> = Rest,
-    <<Res:32>> = <<0:1,I:1,Int2:6,Int3:6,Int4:6,Int5:6,Int6:6>>,
-    Res;
-utf8_binary_char(Err) ->
-    {error,{asn1,{bad_utf8_character_encoding,Err}}}.
-
-
-%% macros used for utf8 encoding
--define(bit1to6_into_utf8byte(I),16#80 bor (I band 16#3f)).
--define(bit7to12_into_utf8byte(I),16#80 bor ((I band 16#fc0) bsr 6)).
--define(bit13to18_into_utf8byte(I),16#80 bor ((I band 16#3f000) bsr 12)).
--define(bit19to24_into_utf8byte(I),16#80 bor ((Int band 16#fc0000) bsr 18)).
--define(bit25to30_into_utf8byte(I),16#80 bor ((Int band 16#3f000000) bsr 24)).
-
-%% utf8_list_to_binary/1 transforms a list of integers to a
-%% binary. Each element in the input list has the unicode (integer)
-%% value of an utf8 character. 
-%% The return value is either {ok,Bin} or {error,Reason}. The
-%% resulting binary is utf8 encoded.
-utf8_list_to_binary(List) ->
-    utf8_list_to_binary(List,[]).
-
-utf8_list_to_binary([],Acc) when is_list(Acc) ->
-    {ok,list_to_binary(lists:reverse(Acc))};
-utf8_list_to_binary([],Acc) ->
-    {error,{asn1,Acc}};
-utf8_list_to_binary([H|T],Acc) ->
-    case catch utf8_encode(H,Acc) of
-	NewAcc when is_list(NewAcc) -> 
-	    utf8_list_to_binary(T,NewAcc);
-	Err -> Err
-    end.
-
-
-utf8_encode(Int,Acc) when Int < 128 ->
-    %% range 16#00000000 - 16#0000007f
-    %% utf8 encoding: 0xxxxxxx
-    [Int|Acc];
-utf8_encode(Int,Acc) when Int < 16#800 ->
-    %% range 16#00000080 - 16#000007ff
-    %% utf8 encoding: 110xxxxx 10xxxxxx
-    [?bit1to6_into_utf8byte(Int),16#c0 bor (Int bsr 6)|Acc];
-utf8_encode(Int,Acc) when Int < 16#10000 ->
-    %% range 16#00000800 - 16#0000ffff
-    %% utf8 encoding: 1110xxxx 10xxxxxx 10xxxxxx
-    [?bit1to6_into_utf8byte(Int),?bit7to12_into_utf8byte(Int),
-     16#e0 bor ((Int band 16#f000) bsr 12)|Acc];
-utf8_encode(Int,Acc) when Int < 16#200000 ->
-    %% range 16#00010000 - 16#001fffff
-    %% utf8 encoding: 11110xxx 10xxxxxx 10xxxxxx 10xxxxxx
-    [?bit1to6_into_utf8byte(Int),?bit7to12_into_utf8byte(Int),
-     ?bit13to18_into_utf8byte(Int),
-     16#f0 bor ((Int band 16#1c0000) bsr 18)|Acc];
-utf8_encode(Int,Acc) when Int < 16#4000000 ->
-    %% range 16#00200000 - 16#03ffffff
-    %% utf8 encoding: 111110xx 10xxxxxx 10xxxxxx 10xxxxxx 10xxxxxx
-    [?bit1to6_into_utf8byte(Int),?bit7to12_into_utf8byte(Int),
-     ?bit13to18_into_utf8byte(Int),?bit19to24_into_utf8byte(Int),
-     16#f8 bor ((Int band 16#3000000) bsr 24)|Acc];
-utf8_encode(Int,Acc) ->
-    %% range 16#04000000 - 16#7fffffff
-    %% utf8 encoding: 1111110x 10xxxxxx ...(total 6 bytes) 10xxxxxx
-    [?bit1to6_into_utf8byte(Int),?bit7to12_into_utf8byte(Int),
-     ?bit13to18_into_utf8byte(Int),?bit19to24_into_utf8byte(Int),
-     ?bit25to30_into_utf8byte(Int),
-     16#fc bor ((Int band 16#40000000) bsr 30)|Acc].
diff --git a/lib/asn1/test/asn1_SUITE_data/extensionAdditionGroup.erl b/lib/asn1/test/asn1_SUITE_data/extensionAdditionGroup.erl
index 6cf8ecf45..cd6c74b99 100644
--- a/lib/asn1/test/asn1_SUITE_data/extensionAdditionGroup.erl
+++ b/lib/asn1/test/asn1_SUITE_data/extensionAdditionGroup.erl
@@ -120,10 +120,10 @@ run3(Erule) ->
         asn1_NOVALUE,asn1_NOVALUE,asn1_NOVALUE},
        asn1_NOVALUE,asn1_NOVALUE}}}}}}},
         io:format("~p:~p~n",[Erule,Val]),
-    {ok,List}= asn1rt:encode('EUTRA-RRC-Definitions','DL-DCCH-Message',Val),
+    {ok,List}= 'EUTRA-RRC-Definitions':encode('DL-DCCH-Message',Val),
     Enc = iolist_to_binary(List),
     io:format("Result from encode:~n~p~n",[Enc]),
-    {ok,Val2} = asn1rt:decode('EUTRA-RRC-Definitions','DL-DCCH-Message',Enc),
+    {ok,Val2} = 'EUTRA-RRC-Definitions':decode('DL-DCCH-Message', Enc),
     io:format("Result from decode:~n~p~n",[Val2]),
     case Val2 of
 	Val -> ok;
diff --git a/lib/asn1/test/asn1_SUITE_data/testobj.erl b/lib/asn1/test/asn1_SUITE_data/testobj.erl
index a0e00f831..e547ea457 100644
--- a/lib/asn1/test/asn1_SUITE_data/testobj.erl
+++ b/lib/asn1/test/asn1_SUITE_data/testobj.erl
@@ -1410,16 +1410,14 @@ int2bin(Int) ->
 %%%%%%%%%%%%%%%%% wrappers %%%%%%%%%%%%%%%%%%%%%%%%
 
 wrapper_encode(Module,Type,Value) ->
-    case asn1rt:encode(Module,Type,Value) of
-	{ok,X} when binary(X) ->
+    case Module:encode(Type, Value) of
+	{ok,X} when is_binary(X) ->
 	    {ok, binary_to_list(X)};
-	{ok,X} ->
-	    {ok, binary_to_list(list_to_binary(X))};
 	Error ->
 	    Error
     end.
 
 wrapper_decode(Module, Type, Bytes) when is_binary(Bytes) ->
-    asn1rt:decode(Module, Type, Bytes);
+    Module:decode(Type, Bytes);
 wrapper_decode(Module, Type, Bytes) when is_list(Bytes) ->
-    asn1rt:decode(Module, Type, list_to_binary(Bytes)).
+    Module:decode(Type, list_to_binary(Bytes)).
diff --git a/lib/asn1/test/testPrimStrings.erl b/lib/asn1/test/testPrimStrings.erl
index cb97655c1..b7f032330 100644
--- a/lib/asn1/test/testPrimStrings.erl
+++ b/lib/asn1/test/testPrimStrings.erl
@@ -19,8 +19,6 @@
 %%
 %%
 -module(testPrimStrings).
--compile([{nowarn_deprecated_function,{asn1rt,utf8_list_to_binary,1}},
-	  {nowarn_deprecated_function,{asn1rt,utf8_binary_to_list,1}}]).
 
 -export([bit_string/2]).
 -export([octet_string/1]).
@@ -756,19 +754,21 @@ utf8_string(_Rules) ->
 		 16#800,
 		 16#ffff,
 		 16#10000,
-		 16#1fffff,
-		 16#200000,
-		 16#3ffffff,
-		 16#4000000,
-		 16#7fffffff],
+		 16#1ffff,
+		 16#20000,
+		 16#2ffff,
+                 16#e0000,
+                 16#effff,
+                 16#F0000,
+		 16#10ffff],
     [begin
-	 {ok,UTF8} = asn1rt:utf8_list_to_binary([Char]),
-	 {ok,[Char]} = asn1rt:utf8_binary_to_list(UTF8),
+	 UTF8 = unicode:characters_to_binary([Char]),
+	 [Char] = unicode:characters_to_list([UTF8]),
 	 roundtrip('UTF', UTF8)
      end || Char <- AllRanges],
 
-    {ok,UTF8} = asn1rt:utf8_list_to_binary(AllRanges),
-    {ok,AllRanges} = asn1rt:utf8_binary_to_list(UTF8),
+    UTF8 = unicode:characters_to_binary(AllRanges),
+    AllRanges = unicode:characters_to_list(UTF8),
     roundtrip('UTF', UTF8),
     ok.
 
diff --git a/lib/stdlib/src/otp_internal.erl b/lib/stdlib/src/otp_internal.erl
index 4161ced9a..f4257fb57 100644
--- a/lib/stdlib/src/otp_internal.erl
+++ b/lib/stdlib/src/otp_internal.erl
@@ -408,7 +408,7 @@ obsolete_1(docb_xml_check, _, _) ->
 
 %% Added in R15B
 obsolete_1(asn1rt, F, _) when F == load_driver; F == unload_driver ->
-    {deprecated,"deprecated (will be removed in OTP 18); has no effect as drivers are no longer used"};
+    {removed,"removed (will be removed in OTP 18); has no effect as drivers are no longer used"};
 obsolete_1(ssl, pid, 1) ->
     {removed,"was removed in R16; is no longer needed"};
 obsolete_1(inviso, _, _) ->
@@ -463,21 +463,23 @@ obsolete_1(wxCursor, new, 4) ->
 
 %% Added in OTP 17.
 obsolete_1(asn1ct, decode,3) ->
-    {deprecated,"deprecated; use Mod:decode/2 instead"};
+    {removed,"removed; use Mod:decode/2 instead"};
+obsolete_1(asn1ct, encode, 2) ->
+    {removed,"removed; use Mod:encode/2 instead"};
 obsolete_1(asn1ct, encode, 3) ->
-    {deprecated,"deprecated; use Mod:encode/2 instead"};
+    {removed,"removed; use Mod:encode/2 instead"};
 obsolete_1(asn1rt, decode,3) ->
-    {deprecated,"deprecated; use Mod:decode/2 instead"};
+    {removed,"removed; use Mod:decode/2 instead"};
 obsolete_1(asn1rt, encode, 2) ->
-    {deprecated,"deprecated; use Mod:encode/2 instead"};
+    {removed,"removed; use Mod:encode/2 instead"};
 obsolete_1(asn1rt, encode, 3) ->
-    {deprecated,"deprecated; use Mod:encode/2 instead"};
+    {removed,"removed; use Mod:encode/2 instead"};
 obsolete_1(asn1rt, info, 1) ->
-    {deprecated,"deprecated; use Mod:info/0 instead"};
+    {removed,"removed; use Mod:info/0 instead"};
 obsolete_1(asn1rt, utf8_binary_to_list, 1) ->
-    {deprecated,{unicode,characters_to_list,1}};
+    {removed,{unicode,characters_to_list,1},"OTP 20"};
 obsolete_1(asn1rt, utf8_list_to_binary, 1) ->
-    {deprecated,{unicode,characters_to_binary,1}};
+    {removed,{unicode,characters_to_binary,1},"OTP 20"};
 
 %% Added in OTP 18.
 obsolete_1(core_lib, get_anno, 1) ->
-- 
2.11.0

openSUSE Build Service is sponsored by