File 1271-Remove-support-for-emitting-code-compatible-with-OTP.patch of Package erlang

From 93768d349b7de2c505e30f8cde4c897e5ebe3c84 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Bj=C3=B6rn=20Gustavsson?= <bjorn@erlang.org>
Date: Wed, 20 Aug 2025 08:27:19 +0200
Subject: [PATCH] Remove support for emitting code compatible with OTP 25

Since OTP 29 will no longer support running code compiled for
OTP 25, we remove compiler support for generating code for OTP 25,
as well as tests testing compatibility with OTP 25.
---
 .gitignore                                    |  6 +----
 erts/.gitignore                               |  2 +-
 erts/emulator/test/Makefile                   | 19 ++------------
 erts/emulator/test/bs_match_int_SUITE.erl     |  2 --
 erts/emulator/test/bs_utf_SUITE.erl           |  1 -
 erts/emulator/test/erts_test_utils.erl        |  7 +----
 erts/test/upgrade_SUITE.erl                   |  7 +----
 lib/common_test/src/test_server_node.erl      |  7 +----
 lib/compiler/src/beam_core_to_ssa.erl         | 26 +++++++------------
 lib/compiler/src/beam_ssa_opt.erl             |  4 +--
 lib/compiler/src/compile.erl                  | 14 +++++-----
 lib/compiler/test/Makefile                    | 16 ++++++------
 lib/compiler/test/beam_debug_info_SUITE.erl   |  2 +-
 lib/compiler/test/bs_bincomp_SUITE.erl        | 20 +-------------
 lib/compiler/test/bs_construct_SUITE.erl      | 18 +------------
 lib/compiler/test/bs_match_SUITE.erl          | 23 ++--------------
 lib/compiler/test/bs_utf_SUITE.erl            | 18 +------------
 lib/compiler/test/compile_SUITE.erl           | 12 +++------
 .../test/property_test/compile_prop.erl       |  1 -
 lib/kernel/test/global_SUITE.erl              |  7 +----
 lib/kernel/test/kernel_SUITE.erl              |  7 +----
 lib/observer/test/crashdump_helper.erl        |  7 +----
 lib/sasl/test/sasl_SUITE.erl                  |  7 +----
 lib/stdlib/test/stdlib_SUITE.erl              |  7 +----
 24 files changed, 47 insertions(+), 193 deletions(-)

diff --git a/erts/emulator/test/Makefile b/erts/emulator/test/Makefile
index 2c4181d70f..4ee53e97c2 100644
--- a/erts/emulator/test/Makefile
+++ b/erts/emulator/test/Makefile
@@ -157,15 +157,6 @@ NO_OPT= bs_bincomp \
 	guard \
 	map
 
-R25= \
-	bs_bincomp \
-	bs_construct \
-	bs_match_bin \
-	bs_match_int \
-	bs_match_tail \
-	bs_match_misc \
-	bs_utf
-
 STRIPPED_TYPES= \
 	bs_bincomp \
 	bs_construct \
@@ -178,9 +169,6 @@ STRIPPED_TYPES= \
 NO_OPT_MODULES= $(NO_OPT:%=%_no_opt_SUITE)
 NO_OPT_ERL_FILES= $(NO_OPT_MODULES:%=%.erl)
 
-R25_MODULES= $(R25:%=%_r25_SUITE)
-R25_ERL_FILES= $(R25_MODULES:%=%.erl)
-
 STRIPPED_TYPES_MODULES= $(STRIPPED_TYPES:%=%_stripped_types_SUITE)
 STRIPPED_TYPES_ERL_FILES= $(STRIPPED_TYPES_MODULES:%=%.erl)
 
@@ -221,13 +209,11 @@ ERL_COMPILE_FLAGS := $(filter-out +deterministic,$($(ERL_COMPILE_FLAGS)))
 # ----------------------------------------------------
 
 make_emakefile: $(NO_OPT_ERL_FILES) \
-  $(KERNEL_ERL_FILES) $(R25_ERL_FILES) $(STRIPPED_TYPES_ERL_FILES)
+  $(KERNEL_ERL_FILES) $(STRIPPED_TYPES_ERL_FILES)
 	$(ERL_TOP)/make/make_emakefile $(ERL_COMPILE_FLAGS) +compressed -o$(EBIN) \
 	$(MODULES) $(STDLIB_MODULES) $(KERNEL_MODULES) >> $(EMAKEFILE)
 	$(ERL_TOP)/make/make_emakefile +no_copt +no_postopt +no_ssa_opt +no_bsm_opt \
         $(ERL_COMPILE_FLAGS) -o$(EBIN) $(NO_OPT_MODULES) >> $(EMAKEFILE)
-	$(ERL_TOP)/make/make_emakefile +r25 \
-        $(ERL_COMPILE_FLAGS) -o$(EBIN) $(R25_MODULES) >> $(EMAKEFILE)
 	$(ERL_TOP)/make/make_emakefile +strip_types \
         $(ERL_COMPILE_FLAGS) -o$(EBIN) $(STRIPPED_TYPES_MODULES) >> $(EMAKEFILE)
 
@@ -251,7 +237,7 @@ targets: $(TARGET_FILES)
 %_no_opt_SUITE.erl: %_SUITE.erl
 	sed -e 's;-module($(basename $<));-module($(basename $@));' $< > $@
 
-%_r25_SUITE.erl: %_SUITE.erl
+%_r26_SUITE.erl: %_SUITE.erl
 	sed -e 's;-module($(basename $<));-module($(basename $@));' $< > $@
 
 %_stripped_types_SUITE.erl: %_SUITE.erl
@@ -270,7 +256,6 @@ release_tests_spec: make_emakefile
 		$(ERL_FILES) "$(RELSYSDIR)"
 	$(INSTALL_DATA) $(NO_OPT_ERL_FILES) "$(RELSYSDIR)"
 	$(INSTALL_DATA) $(KERNEL_ERL_FILES) "$(RELSYSDIR)"
-	$(INSTALL_DATA) $(R25_ERL_FILES) "$(RELSYSDIR)"
 	$(INSTALL_DATA) $(STRIPPED_TYPES_ERL_FILES) "$(RELSYSDIR)"
 	chmod -R u+w "$(RELSYSDIR)"
 	tar cf - *_SUITE_data property_test | (cd "$(RELSYSDIR)"; tar xf -)
diff --git a/erts/emulator/test/bs_match_int_SUITE.erl b/erts/emulator/test/bs_match_int_SUITE.erl
index 646d03c239..ac6dbd8527 100644
--- a/erts/emulator/test/bs_match_int_SUITE.erl
+++ b/erts/emulator/test/bs_match_int_SUITE.erl
@@ -847,8 +847,6 @@ match_huge_int(Config) when is_list(Config) ->
             {skip, "unoptimized code would use too much memory"};
         bs_match_int_SUITE ->
             do_match_huge_int();
-        bs_match_int_r25_SUITE ->
-            do_match_huge_int();
         bs_match_int_stripped_types_SUITE ->
             do_match_huge_int()
     end.
diff --git a/erts/emulator/test/bs_utf_SUITE.erl b/erts/emulator/test/bs_utf_SUITE.erl
index f3c30334ec..224fea6913 100644
--- a/erts/emulator/test/bs_utf_SUITE.erl
+++ b/erts/emulator/test/bs_utf_SUITE.erl
@@ -489,7 +489,6 @@ get_data_dir(Config) ->
     Data = proplists:get_value(data_dir, Config),
     Opts = [{return,list}],
     Suffixes = ["_no_opt_SUITE",
-                "_r25_SUITE",
                 "_stripped_types_SUITE"],
     lists:foldl(fun(Suffix, Acc) ->
                         Opts = [{return,list}],
diff --git a/erts/emulator/test/erts_test_utils.erl b/erts/emulator/test/erts_test_utils.erl
index 06a341596c..2c945c0d9e 100644
--- a/erts/emulator/test/erts_test_utils.erl
+++ b/erts/emulator/test/erts_test_utils.erl
@@ -22,12 +22,7 @@
 
 -module(erts_test_utils).
 
-%% Prior to OTP 26, maybe_expr used to require runtime support. As it's now
-%% enabled by default, all modules are tagged with the feature even when they
-%% don't use it. Therefore, we explicitly disable it until OTP 25 is out of
-%% support.
--feature(maybe_expr, disable).
--compile(r25).
+-compile(r26).
 
 %%
 %% THIS MODULE IS ALSO USED BY *OTHER* APPLICATIONS TEST CODE
diff --git a/erts/test/upgrade_SUITE.erl b/erts/test/upgrade_SUITE.erl
index 435cf910ca..bc93fd7894 100644
--- a/erts/test/upgrade_SUITE.erl
+++ b/erts/test/upgrade_SUITE.erl
@@ -20,12 +20,7 @@
 %% %CopyrightEnd%
 -module(upgrade_SUITE).
 
-%% Prior to OTP 26, maybe_expr used to require runtime support. As it's now
-%% enabled by default, all modules are tagged with the feature even when they
-%% don't use it. Therefore, we explicitly disable it until OTP 25 is out of
-%% support.
--feature(maybe_expr, disable).
--compile(r25).
+-compile(r26).
 
 -compile(export_all).
 
diff --git a/lib/common_test/src/test_server_node.erl b/lib/common_test/src/test_server_node.erl
index 2d7d3fabc5..458e6c5b47 100644
--- a/lib/common_test/src/test_server_node.erl
+++ b/lib/common_test/src/test_server_node.erl
@@ -22,12 +22,7 @@
 -module(test_server_node).
 -moduledoc false.
 
-%% Prior to OTP 26, maybe_expr used to require runtime support. As it's now
-%% enabled by default, all modules are tagged with the feature even when they
-%% don't use it. Therefore, we explicitly disable it until OTP 25 is out of
-%% support.
--feature(maybe_expr, disable).
--compile(r25).
+-compile(r26).
 
 %% Test Controller interface
 -export([is_release_available/1, find_release/1]).
diff --git a/lib/compiler/src/beam_core_to_ssa.erl b/lib/compiler/src/beam_core_to_ssa.erl
index e5d5149a05..fd7f80bfe6 100644
--- a/lib/compiler/src/beam_core_to_ssa.erl
+++ b/lib/compiler/src/beam_core_to_ssa.erl
@@ -150,7 +150,6 @@ get_anno(#cg_select{anno=Anno}) -> Anno.
                funs=[],                         %Fun functions
                free=#{},                        %Free variables
                ws=[]   :: [warning()],          %Warnings.
-               no_min_max_bifs=false :: boolean(),
                beam_debug_info=false :: boolean()
               }).
 
@@ -160,10 +159,8 @@ get_anno(#cg_select{anno=Anno}) -> Anno.
 module(#c_module{name=#c_literal{val=Mod},exports=Es,attrs=As,defs=Fs}, Options) ->
     Kas = attributes(As),
     Kes = map(fun (#c_var{name={_,_}=Fname}) -> Fname end, Es),
-    NoMinMaxBifs = proplists:get_bool(no_min_max_bifs, Options),
     DebugInfo = proplists:get_bool(beam_debug_info, Options),
     St0 = #kern{module=Mod,
-                no_min_max_bifs=NoMinMaxBifs,
                 beam_debug_info=DebugInfo},
     {Kfs,St} = mapfoldl(fun function/2, St0, Fs),
     Body = Kfs ++ St#kern.funs,
@@ -363,7 +360,7 @@ expr(#c_case{arg=Ca,clauses=Ccs}, Sub, St0) ->
 expr(#c_apply{anno=A,op=Cop,args=Cargs}, Sub, St) ->
     c_apply(A, Cop, Cargs, Sub, St);
 expr(#c_call{anno=A,module=M0,name=F0,args=Cargs}, Sub, St0) ->
-    case call_type(M0, F0, Cargs, St0) of
+    case call_type(M0, F0, Cargs) of
         bif ->
             #c_literal{val=Name} = F0,
             {Args,Ap,St} = atomic_list(Cargs, Sub, St0),
@@ -1027,25 +1024,20 @@ make_vars(Vs) -> [#b_var{name=V} || V <- Vs].
 
 %% call_type(Mod, Name, [Arg], State) -> bif | call | is_record | error.
 
-call_type(#c_literal{val=M}, #c_literal{val=F}, As, St) when is_atom(M), is_atom(F) ->
+call_type(#c_literal{val=M}, #c_literal{val=F}, As) when is_atom(M), is_atom(F) ->
     case is_guard_bif(M, F, As) of
         false ->
             call;
         true ->
-            %% The guard BIFs min/2 and max/2 were introduced in
-            %% Erlang/OTP 26. If we are compiling for an earlier
-            %% version, we must translate them as call instructions.
-            case {M,F,St#kern.no_min_max_bifs} of
-                {erlang,min,true} -> call;
-                {erlang,max,true} -> call;
-                {erlang,is_record,_} when length(As) =:= 3 -> is_record;
-                {erlang,_,_} -> bif
+            case {M,F} of
+                {erlang,is_record} when length(As) =:= 3 -> is_record;
+                {erlang,_} -> bif
             end
     end;
-call_type(#c_var{}, #c_literal{val=A}, _, _) when is_atom(A) -> call;
-call_type(#c_literal{val=A}, #c_var{}, _, _) when is_atom(A) -> call;
-call_type(#c_var{}, #c_var{}, _, _) -> call;
-call_type(_, _, _, _) -> error.
+call_type(#c_var{}, #c_literal{val=A}, _) when is_atom(A) -> call;
+call_type(#c_literal{val=A}, #c_var{}, _) when is_atom(A) -> call;
+call_type(#c_var{}, #c_var{}, _) -> call;
+call_type(_, _, _) -> error.
 
 %% is_guard_bif(Mod, Name, Args) -> true | false.
 %%  Test whether this function is a guard BIF.
diff --git a/lib/compiler/src/beam_ssa_opt.erl b/lib/compiler/src/beam_ssa_opt.erl
index 1b971a5026..c030bdd5c9 100644
--- a/lib/compiler/src/beam_ssa_opt.erl
+++ b/lib/compiler/src/beam_ssa_opt.erl
@@ -323,9 +323,7 @@ late_epilogue_passes(Opts) ->
 passes_1(Ps, Opts0) ->
     Negations = [{list_to_atom("no_"++atom_to_list(N)),N} ||
                     {N,_} <:- Ps],
-    Expansions = [{no_bs_match,[no_ssa_opt_bs_ensure,no_bs_match]}],
-    Opts = proplists:normalize(Opts0, [{expand,Expansions},
-                                       {negations,Negations}]),
+    Opts = proplists:normalize(Opts0, [{negations,Negations}]),
     [case proplists:get_value(Name, Opts, true) of
          true ->
              P;
diff --git a/lib/compiler/src/compile.erl b/lib/compiler/src/compile.erl
index 7bfe1f737f..ae5a57f100 100644
--- a/lib/compiler/src/compile.erl
+++ b/lib/compiler/src/compile.erl
@@ -1075,9 +1075,6 @@ expand_opt(report, Os) ->
     [report_errors,report_warnings|Os];
 expand_opt(return, Os) ->
     [return_errors,return_warnings|Os];
-expand_opt(r25, Os) ->
-    [no_ssa_opt_update_tuple, no_bs_match, no_min_max_bifs |
-     expand_opt(r26, Os)];
 expand_opt(r26, Os) ->
     [no_bsm_opt | expand_opt(r27, Os)];
 expand_opt(r27, Os) ->
@@ -2405,16 +2402,19 @@ is_obsolete(r21) -> true;
 is_obsolete(r22) -> true;
 is_obsolete(r23) -> true;
 is_obsolete(r24) -> true;
+is_obsolete(r25) -> true;
 is_obsolete(no_badrecord) -> true;
 is_obsolete(no_bs_create_bin) -> true;
+is_obsolete(no_bs_match) -> true;
 is_obsolete(no_bsm3) -> true;
 is_obsolete(no_get_hd_tl) -> true;
-is_obsolete(no_put_tuple2) -> true;
-is_obsolete(no_utf8_atoms) -> true;
-is_obsolete(no_swap) -> true;
 is_obsolete(no_init_yregs) -> true;
-is_obsolete(no_shared_fun_wrappers) -> true;
 is_obsolete(no_make_fun3) -> true;
+is_obsolete(no_min_max_bifs) -> true;
+is_obsolete(no_put_tuple2) -> true;
+is_obsolete(no_shared_fun_wrappers) -> true;
+is_obsolete(no_swap) -> true;
+is_obsolete(no_utf8_atoms) -> true;
 is_obsolete(_) -> false.
 
 core(Forms, #compile{options=Opts}=St) ->
diff --git a/lib/compiler/test/Makefile b/lib/compiler/test/Makefile
index 6cea67a16e..e7ae786df7 100644
--- a/lib/compiler/test/Makefile
+++ b/lib/compiler/test/Makefile
@@ -139,7 +139,7 @@ INLINE= \
 	receive \
 	record
 
-R25= \
+R26= \
 	bs_construct \
 	bs_match \
 	bs_utf \
@@ -171,8 +171,8 @@ NO_CORE_SSA_OPT_MODULES= $(NO_OPT:%=%_no_copt_ssa_SUITE)
 NO_CORE_SSA_OPT_ERL_FILES= $(NO_CORE_SSA_OPT_MODULES:%=%.erl)
 INLINE_MODULES= $(INLINE:%=%_inline_SUITE)
 INLINE_ERL_FILES= $(INLINE_MODULES:%=%.erl)
-R25_MODULES= $(R25:%=%_r25_SUITE)
-R25_ERL_FILES= $(R25_MODULES:%=%.erl)
+R26_MODULES= $(R26:%=%_r26_SUITE)
+R26_ERL_FILES= $(R26_MODULES:%=%.erl)
 NO_MOD_OPT_MODULES= $(NO_MOD_OPT:%=%_no_module_opt_SUITE)
 NO_MOD_OPT_ERL_FILES= $(NO_MOD_OPT_MODULES:%=%.erl)
 NO_SSA_OPT_MODULES= $(NO_SSA_OPT:%=%_no_ssa_opt_SUITE)
@@ -221,7 +221,7 @@ make_emakefile: $(NO_BOOL_OPT_ERL_FILES) $(NO_OPT_ERL_FILES) \
                 $(NO_CORE_OPT_ERL_FILES) $(NO_CORE_SSA_OPT_ERL_FILES) \
                 $(INLINE_ERL_FILES) $(NO_MOD_OPT_ERL_FILES) \
                 $(NO_TYPE_OPT_ERL_FILES) $(DIALYZER_ERL_FILES) \
-                $(COVER_ERL_FILES) $(R25_ERL_FILES)
+                $(COVER_ERL_FILES) $(R26_ERL_FILES)
 	$(ERL_TOP)/make/make_emakefile $(ERL_COMPILE_FLAGS) -o$(EBIN) $(MODULES) \
 	  > $(EMAKEFILE)
 	$(ERL_TOP)/make/make_emakefile +no_bool_opt $(ERL_COMPILE_FLAGS) \
@@ -238,8 +238,8 @@ make_emakefile: $(NO_BOOL_OPT_ERL_FILES) $(NO_OPT_ERL_FILES) \
 	  -o$(EBIN) $(NO_CORE_SSA_OPT_MODULES) >> $(EMAKEFILE)
 	$(ERL_TOP)/make/make_emakefile +inline $(ERL_COMPILE_FLAGS) \
 	  -o$(EBIN) $(INLINE_MODULES) >> $(EMAKEFILE)
-	$(ERL_TOP)/make/make_emakefile +r25 $(ERL_COMPILE_FLAGS) \
-	  -o$(EBIN) $(R25_MODULES) >> $(EMAKEFILE)
+	$(ERL_TOP)/make/make_emakefile +r26 $(ERL_COMPILE_FLAGS) \
+	  -o$(EBIN) $(R26_MODULES) >> $(EMAKEFILE)
 	$(ERL_TOP)/make/make_emakefile +no_module_opt $(ERL_COMPILE_FLAGS) \
 	  -o$(EBIN) $(NO_MOD_OPT_MODULES) >> $(EMAKEFILE)
 	$(ERL_TOP)/make/make_emakefile +from_core $(ERL_COMPILE_FLAGS) \
@@ -286,7 +286,7 @@ docs:
 %_inline_SUITE.erl: %_SUITE.erl
 	sed -e 's;-module($(basename $<));-module($(basename $@));' $< > $@
 
-%_r25_SUITE.erl: %_SUITE.erl
+%_r26_SUITE.erl: %_SUITE.erl
 	sed -e 's;-module($(basename $<));-module($(basename $@));' $< > $@
 
 %_no_module_opt_SUITE.erl: %_SUITE.erl
@@ -317,7 +317,7 @@ release_tests_spec: make_emakefile
 		$(NO_OPT_ERL_FILES) \
 		$(POST_OPT_ERL_FILES) \
 		$(INLINE_ERL_FILES) \
-	        $(R25_ERL_FILES) \
+	        $(R26_ERL_FILES) \
 		$(NO_CORE_OPT_ERL_FILES) \
 		$(NO_CORE_SSA_OPT_ERL_FILES) \
 		$(NO_MOD_OPT_ERL_FILES) \
diff --git a/lib/compiler/test/beam_debug_info_SUITE.erl b/lib/compiler/test/beam_debug_info_SUITE.erl
index 092bacf2a0..498d373784 100644
--- a/lib/compiler/test/beam_debug_info_SUITE.erl
+++ b/lib/compiler/test/beam_debug_info_SUITE.erl
@@ -792,7 +792,7 @@ get_unique_beam_files() ->
     F = fun IsCloned(ModString) ->
                 case ModString of
                     "_dialyzer_SUITE" -> true;
-                    "_r25_SUITE" -> true;
+                    "_r26_SUITE" -> true;
                     [_|T] -> IsCloned(T);
                     _ -> false
                 end
diff --git a/lib/compiler/test/bs_bincomp_SUITE.erl b/lib/compiler/test/bs_bincomp_SUITE.erl
index 32c9c9ceb9..dcc714179d 100644
--- a/lib/compiler/test/bs_bincomp_SUITE.erl
+++ b/lib/compiler/test/bs_bincomp_SUITE.erl
@@ -26,7 +26,6 @@
 
 -export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
 	 init_per_group/2,end_per_group/2,
-         verify_highest_opcode/1,
 	 byte_aligned/1,bit_aligned/1,extended_byte_aligned/1,
 	 extended_bit_aligned/1,mixed/1,filters/1,trim_coverage/1,
 	 nomatch/1,sizes/1,general_expressions/1,
@@ -38,8 +37,7 @@
 suite() -> [{ct_hooks,[ts_install_cth]}].
 
 all() ->
-    [verify_highest_opcode,
-     byte_aligned, bit_aligned, extended_byte_aligned,
+    [byte_aligned, bit_aligned, extended_byte_aligned,
      extended_bit_aligned, mixed, filters, trim_coverage,
      nomatch, sizes, general_expressions,
      no_generator, zero_pattern, multiple_segments,
@@ -61,20 +59,6 @@ init_per_group(_GroupName, Config) ->
 end_per_group(_GroupName, Config) ->
 	Config.
 
-verify_highest_opcode(_Config) ->
-    case ?MODULE of
-        bs_bincomp_r25_SUITE ->
-            {ok,Beam} = file:read_file(code:which(?MODULE)),
-            case test_lib:highest_opcode(Beam) of
-                Highest when Highest =< 180 ->
-                    ok;
-                TooHigh ->
-                    ct:fail({too_high_opcode,TooHigh})
-            end;
-        _ ->
-            ok
-    end.
-
 byte_aligned(Config) when is_list(Config) ->
     cs_init(),
     <<"abcdefg">> = cs(<< <<(X+32)>> || <<X>> <= <<"ABCDEFG">> >>),
@@ -728,8 +712,6 @@ cs(Bin) ->
             ok;
         bs_bincomp_post_opt_SUITE ->
             ok;
-        bs_bincomp_r25_SUITE ->
-            ok;
         bs_bincomp_r26_SUITE ->
             ok;
         _ ->
diff --git a/lib/compiler/test/bs_construct_SUITE.erl b/lib/compiler/test/bs_construct_SUITE.erl
index b390febda3..7afad7528d 100644
--- a/lib/compiler/test/bs_construct_SUITE.erl
+++ b/lib/compiler/test/bs_construct_SUITE.erl
@@ -29,7 +29,6 @@
 -export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, 
 	 init_per_group/2,end_per_group/2,
 	 init_per_testcase/2,end_per_testcase/2,
-         verify_highest_opcode/1,
 	 two/1,test1/1,fail/1,float_bin/1,in_guard/1,in_catch/1,
 	 nasty_literals/1,coerce_to_float/1,side_effect/1,
 	 opt/1,otp_7556/1,float_arith/1,otp_8054/1,
@@ -46,8 +45,7 @@ all() ->
 
 groups() ->
     [{p,[parallel],
-      [verify_highest_opcode,
-       two,test1,fail,float_bin,in_guard,in_catch,
+      [two,test1,fail,float_bin,in_guard,in_catch,
        nasty_literals,side_effect,opt,otp_7556,float_arith,
        otp_8054,strings,bad_size,private_append]}].
 
@@ -72,20 +70,6 @@ init_per_testcase(Case, Config) when is_atom(Case), is_list(Config) ->
 end_per_testcase(Case, Config) when is_atom(Case), is_list(Config) ->
     ok.
 
-verify_highest_opcode(_Config) ->
-    case ?MODULE of
-        bs_construct_r25_SUITE ->
-            {ok,Beam} = file:read_file(code:which(?MODULE)),
-            case test_lib:highest_opcode(Beam) of
-                Highest when Highest =< 180 ->
-                    ok;
-                TooHigh ->
-                    ct:fail({too_high_opcode,TooHigh})
-            end;
-        _ ->
-            ok
-    end.
-
 two(Config) when is_list(Config) ->
     <<0,1,2,3,4,6,7,8,9>> = two_1([0], [<<1,2,3,4>>,<<6,7,8,9>>]),
     ok.
diff --git a/lib/compiler/test/bs_match_SUITE.erl b/lib/compiler/test/bs_match_SUITE.erl
index bb08fb645f..1638281688 100644
--- a/lib/compiler/test/bs_match_SUITE.erl
+++ b/lib/compiler/test/bs_match_SUITE.erl
@@ -29,7 +29,7 @@
 -export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, 
 	 init_per_group/2,end_per_group/2,
 	 init_per_testcase/2,end_per_testcase/2,
-         verify_highest_opcode/1, expand_and_squeeze/1,
+         expand_and_squeeze/1,
 	 size_shadow/1,int_float/1,otp_5269/1,null_fields/1,wiger/1,
 	 bin_tail/1,save_restore/1,
 	 partitioned_bs_match/1,function_clause/1,
@@ -76,8 +76,7 @@ all() ->
 
 groups() -> 
     [{p,test_lib:parallel(),
-      [verify_highest_opcode,
-       size_shadow,int_float,otp_5269,null_fields,wiger,
+      [size_shadow,int_float,otp_5269,null_fields,wiger,
        bin_tail,save_restore,expand_and_squeeze,
        partitioned_bs_match,function_clause,unit,
        shared_sub_bins,bin_and_float,dec_subidentifiers,
@@ -125,24 +124,6 @@ init_per_testcase(Case, Config) when is_atom(Case), is_list(Config) ->
 end_per_testcase(Case, Config) when is_atom(Case), is_list(Config) ->
     ok.
 
-verify_highest_opcode(_Config) ->
-    case ?MODULE of
-        bs_match_r25_SUITE ->
-            {ok,Beam} = file:read_file(code:which(?MODULE)),
-            case test_lib:highest_opcode(Beam) of
-                Highest when Highest =< 180 ->
-                    ok;
-                TooHigh ->
-                    ct:fail({too_high_opcode_for_21,TooHigh})
-            end,
-
-            %% Cover min/max for OTP 25.
-            10 = max(0, min(10, id(42))),
-            ok;
-        _ ->
-            ok
-    end.
-
 size_shadow(Config) when is_list(Config) ->
     %% Originally OTP-5270.
     7 = size_shadow_1(),
diff --git a/lib/compiler/test/bs_utf_SUITE.erl b/lib/compiler/test/bs_utf_SUITE.erl
index acafcbb964..6cf3d6e129 100644
--- a/lib/compiler/test/bs_utf_SUITE.erl
+++ b/lib/compiler/test/bs_utf_SUITE.erl
@@ -24,7 +24,6 @@
 
 -export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
 	 init_per_group/2,end_per_group/2,
-         verify_highest_opcode/1,
 	 utf8_roundtrip/1,unused_utf_char/1,utf16_roundtrip/1,
 	 utf32_roundtrip/1,guard/1,extreme_tripping/1,
 	 literals/1,coverage/1]).
@@ -34,8 +33,7 @@
 suite() -> [{ct_hooks,[ts_install_cth]}].
 
 all() ->
-    [verify_highest_opcode,
-     utf8_roundtrip, unused_utf_char, utf16_roundtrip,
+    [utf8_roundtrip, unused_utf_char, utf16_roundtrip,
      utf32_roundtrip, guard, extreme_tripping, literals,
      coverage].
 
@@ -55,20 +53,6 @@ init_per_group(_GroupName, Config) ->
 end_per_group(_GroupName, Config) ->
     Config.
 
-verify_highest_opcode(_Config) ->
-    case ?MODULE of
-        bs_construct_r25_SUITE ->
-            {ok,Beam} = file:read_file(code:which(?MODULE)),
-            case test_lib:highest_opcode(Beam) of
-                Highest when Highest =< 180 ->
-                    ok;
-                TooHigh ->
-                    ct:fail({too_high_opcode,TooHigh})
-            end;
-        _ ->
-            ok
-    end.
-
 utf8_roundtrip(Config) when is_list(Config) ->
     [utf8_roundtrip_1(P) || P <- utf_data()],
     ok.
diff --git a/lib/compiler/test/compile_SUITE.erl b/lib/compiler/test/compile_SUITE.erl
index f9fe1d5b7e..562e4c21ef 100644
--- a/lib/compiler/test/compile_SUITE.erl
+++ b/lib/compiler/test/compile_SUITE.erl
@@ -1717,12 +1717,6 @@ bc_options(Config) ->
 
     L = [{177, small_float, []},
 
-         {177, small, [no_ssa_opt_record,
-                       no_ssa_opt_float,
-                       no_line_info,
-                       no_type_opt,
-                       no_bs_match]},
-
          {177, funs, [no_ssa_opt_record,
                       no_ssa_opt_float,
                       no_line_info,
@@ -1736,13 +1730,15 @@ bc_options(Config) ->
                      no_line_info,
                      no_type_opt]},
 
-         {178, small, [r25]},
-         {178, big, [r25]},
          {178, funs, []},
          {178, big, []},
 
          {182, small, [r26]},
          {182, small, []},
+         {182, small, [no_ssa_opt_record,
+                       no_ssa_opt_float,
+                       no_line_info,
+                       no_type_opt]},
 
          {183, small, [line_coverage]},
 
diff --git a/lib/compiler/test/property_test/compile_prop.erl b/lib/compiler/test/property_test/compile_prop.erl
index f661b2e879..460fa5f363 100644
--- a/lib/compiler/test/property_test/compile_prop.erl
+++ b/lib/compiler/test/property_test/compile_prop.erl
@@ -84,7 +84,6 @@ spawn_compile(Forms, Options) ->
 compiler_variants() ->
     [
      [ssalint,clint0,clint],
-     [r25,ssalint],
      [r26,ssalint],
      [no_type_opt,ssalint],
      [no_module_opt,ssalint],
diff --git a/lib/kernel/test/global_SUITE.erl b/lib/kernel/test/global_SUITE.erl
index 1deb3d5e15..373ea34242 100644
--- a/lib/kernel/test/global_SUITE.erl
+++ b/lib/kernel/test/global_SUITE.erl
@@ -21,12 +21,7 @@
 %%
 -module(global_SUITE).
 
-%% Prior to OTP 26, maybe_expr used to require runtime support. As it's now
-%% enabled by default, all modules are tagged with the feature even when they
-%% don't use it. Therefore, we explicitly disable it until OTP 25 is out of
-%% support.
--feature(maybe_expr, disable).
--compile(r25). % many_nodes()
+-compile(r26). % many_nodes()
 
 -export([all/0, suite/0, groups/0, 
 	 init_per_suite/1, end_per_suite/1,
diff --git a/lib/kernel/test/kernel_SUITE.erl b/lib/kernel/test/kernel_SUITE.erl
index ac7d410d98..a6d2c49522 100644
--- a/lib/kernel/test/kernel_SUITE.erl
+++ b/lib/kernel/test/kernel_SUITE.erl
@@ -24,12 +24,7 @@
 %%%-----------------------------------------------------------------
 -module(kernel_SUITE).
 
-%% Prior to OTP 26, maybe_expr used to require runtime support. As it's now
-%% enabled by default, all modules are tagged with the feature even when they
-%% don't use it. Therefore, we explicitly disable it until OTP 25 is out of
-%% support.
--feature(maybe_expr, disable).
--compile(r25).
+-compile(r26).
 
 -include_lib("common_test/include/ct.hrl").
 
diff --git a/lib/observer/test/crashdump_helper.erl b/lib/observer/test/crashdump_helper.erl
index 760c56e041..3366c2b682 100644
--- a/lib/observer/test/crashdump_helper.erl
+++ b/lib/observer/test/crashdump_helper.erl
@@ -22,12 +22,7 @@
 
 -module(crashdump_helper).
 
-%% Prior to OTP 26, maybe_expr used to require runtime support. As it's now
-%% enabled by default, all modules are tagged with the feature even when they
-%% don't use it. Therefore, we explicitly disable it until OTP 25 is out of
-%% support.
--feature(maybe_expr, disable).
--compile(r25).
+-compile(r26).
 
 -export([n1_proc/2,remote_proc/2,
          dump_maps/0,create_maps/0,
diff --git a/lib/sasl/test/sasl_SUITE.erl b/lib/sasl/test/sasl_SUITE.erl
index 702e0d5ad8..35dcbce3b7 100644
--- a/lib/sasl/test/sasl_SUITE.erl
+++ b/lib/sasl/test/sasl_SUITE.erl
@@ -21,12 +21,7 @@
 %%
 -module(sasl_SUITE).
 
-%% Prior to OTP 26, maybe_expr used to require runtime support. As it's now
-%% enabled by default, all modules are tagged with the feature even when they
-%% don't use it. Therefore, we explicitly disable it until OTP 25 is out of
-%% support.
--feature(maybe_expr, disable).
--compile(r25).
+-compile(r26).
 
 -include_lib("common_test/include/ct.hrl").
 
diff --git a/lib/stdlib/test/stdlib_SUITE.erl b/lib/stdlib/test/stdlib_SUITE.erl
index 0aec5df75c..62a467f277 100644
--- a/lib/stdlib/test/stdlib_SUITE.erl
+++ b/lib/stdlib/test/stdlib_SUITE.erl
@@ -24,12 +24,7 @@
 %%%-----------------------------------------------------------------
 -module(stdlib_SUITE).
 
-%% Prior to OTP 26, maybe_expr used to require runtime support. As it's now
-%% enabled by default, all modules are tagged with the feature even when they
-%% don't use it. Therefore, we explicitly disable it until OTP 25 is out of
-%% support.
--feature(maybe_expr, disable).
--compile(r25).
+-compile(r26).
 
 -include_lib("common_test/include/ct.hrl").
 -export([all/0, suite/0, init_per_suite/1, end_per_suite/1,
-- 
2.43.0

openSUSE Build Service is sponsored by