File 4861-compiler-Fix-bug-in-nif_start-insertion.patch of Package erlang

From 1d92cc051e6b4536d49ff83527791c90f9885e93 Mon Sep 17 00:00:00 2001
From: Frej Drejhammar <frej.drejhammar@gmail.com>
Date: Mon, 19 Jun 2023 11:50:24 +0200
Subject: [PATCH] compiler: Fix bug in `nif_start` insertion

Commit 724da95cd04d2bc1d6cb89d1988b58b2096d59cd extended the
v3_core-pass to make all functions start with a `nif_start`
instruction when the `nifs` attribute isn't present in the module but
a call to `erlang:load_nif/2` is. The `nif_start` instruction is used
as a flag, allowing later compiler passes to easily identify a NIF.

The initial implementation assumed that a function body could only be
a `#c_seq{}` or a `#c_case{}` and never a `#c_letrec{}`. This patch
extends the v3_core-pass to handle function bodies consisting of a
`#c_letrec{}`. Credits for discovering a test case triggering this
omission goes to Matthew Pope.

Closes #7409
---
 lib/compiler/src/v3_core.erl              |  7 ++++-
 lib/compiler/test/core_SUITE.erl          | 33 +++++++++++++++++++----
 lib/compiler/test/core_SUITE_data/nif.erl |  7 ++++-
 3 files changed, 40 insertions(+), 7 deletions(-)

diff --git a/lib/compiler/src/v3_core.erl b/lib/compiler/src/v3_core.erl
index daf1f63585..a4b2bd0ba8 100644
--- a/lib/compiler/src/v3_core.erl
+++ b/lib/compiler/src/v3_core.erl
@@ -4101,7 +4101,12 @@ insert_nif_start([VF={V,F=#c_fun{body=Body}}|Funs]) ->
         #c_case{} ->
             NifStart = #c_primop{name=#c_literal{val=nif_start},args=[]},
             [{V,F#c_fun{body=#c_seq{arg=NifStart,body=Body}}}
-            |insert_nif_start(Funs)]
+            |insert_nif_start(Funs)];
+        #c_letrec{defs=Defs,body=LetrecBody0}=LR0 ->
+            NifStart = #c_primop{name=#c_literal{val=nif_start},args=[]},
+            LetrecBody = #c_seq{arg=NifStart,body=LetrecBody0},
+            LR = LR0#c_letrec{defs=insert_nif_start(Defs), body=LetrecBody},
+            [{V,F#c_fun{body=LR}}|insert_nif_start(Funs)]
     end;
 insert_nif_start([]) ->
     [].
diff --git a/lib/compiler/test/core_SUITE.erl b/lib/compiler/test/core_SUITE.erl
index 783b1669d1..d2c9d70245 100644
--- a/lib/compiler/test/core_SUITE.erl
+++ b/lib/compiler/test/core_SUITE.erl
@@ -177,6 +177,7 @@ nif(Conf) ->
 	nif_compile_to_cerl(Conf, [{d,'WITH_ATTRIBUTE'},{d,'WITH_LOAD_NIF'}]),
     false = nif_first_instruction_is_nif_start(init, 1, Funs),
     true = nif_first_instruction_is_nif_start(start, 1, Funs),
+    false = nif_first_instruction_is_nif_start(bug0, 1, Funs),
     false = nif_first_instruction_is_nif_start(module_info, 0, Funs),
     false = nif_first_instruction_is_nif_start(module_info, 1, Funs),
     ok.
@@ -186,6 +187,7 @@ no_nif(Conf) ->
     Funs = nif_compile_to_cerl(Conf, [{d,'WITH_LOAD_NIF'}]),
     true = nif_first_instruction_is_nif_start(init, 1, Funs),
     true = nif_first_instruction_is_nif_start(start, 1, Funs),
+    true = nif_first_instruction_is_nif_start(bug0, 1, Funs),
     true = nif_first_instruction_is_nif_start(module_info, 0, Funs),
     true = nif_first_instruction_is_nif_start(module_info, 1, Funs),
     ok.
@@ -195,6 +197,7 @@ no_load_nif(Conf) ->
     Funs = nif_compile_to_cerl(Conf, []),
     false = nif_first_instruction_is_nif_start(init, 1, Funs),
     false = nif_first_instruction_is_nif_start(start, 1, Funs),
+    false = nif_first_instruction_is_nif_start(bug0, 1, Funs),
     false = nif_first_instruction_is_nif_start(module_info, 0, Funs),
     false = nif_first_instruction_is_nif_start(module_info, 1, Funs),
     ok.
@@ -207,11 +210,7 @@ nif_compile_to_cerl(Conf, Flags) ->
 
 nif_first_instruction_is_nif_start(F, A, [{{F,A},Body}|_]) ->
     try
-	Primop = cerl:seq_arg(Body),
-	Name = cerl:primop_name(Primop),
-	0 = cerl:primop_arity(Primop),
-	nif_start = cerl:atom_val(Name),
-	true
+        assert_body_starts_with_nif_start(Body)
     catch
 	error:_ ->
 	    false
@@ -220,3 +219,27 @@ nif_first_instruction_is_nif_start(F, A, [_|Rest]) ->
     nif_first_instruction_is_nif_start(F, A, Rest);
 nif_first_instruction_is_nif_start(_, _, []) ->
     not_found.
+
+%% Return true if the body starts with nif_start or not at all if
+%% not. Descend into letrecs.
+assert_body_starts_with_nif_start(Body0) ->
+    Body = case cerl:is_c_letrec(Body0) of
+               true ->
+                   %% For the compiler generated functions in the
+                   %% defs-part of the letrec, we just check that
+                   %% they start with a nif-start, regardless of
+                   %% their names.
+                   lists:foreach(fun({_, F}) ->
+                                         assert_body_starts_with_nif_start(
+                                           cerl:fun_body(F))
+                                 end, cerl:letrec_defs(Body0)),
+                   %% Return the body of the letrec for checking.
+                   cerl:letrec_body(Body0);
+               false ->
+                   Body0
+           end,
+    Primop = cerl:seq_arg(Body),
+    Name = cerl:primop_name(Primop),
+    0 = cerl:primop_arity(Primop),
+    nif_start = cerl:atom_val(Name),
+    true.
diff --git a/lib/compiler/test/core_SUITE_data/nif.erl b/lib/compiler/test/core_SUITE_data/nif.erl
index 873e20252b..4c57f1f0e9 100644
--- a/lib/compiler/test/core_SUITE_data/nif.erl
+++ b/lib/compiler/test/core_SUITE_data/nif.erl
@@ -1,6 +1,6 @@
 -module(nif).
 
--export([init/1, start/1]).
+-export([init/1, start/1, bug0/1]).
 
 -ifdef(WITH_ATTRIBUTE).
 -nifs([start/1]).
@@ -15,3 +15,8 @@ init(_File) ->
 -endif.
 
 start(_) -> erlang:nif_error(not_loaded).
+
+%% This used to crash the compiler in the v3_core pass as
+%% insert_nif_start/1 did not support letrecs.
+bug0(<<HL:32/signed-integer-big-unit:1, _:HL/binary, _/binary>>) ->
+    <<>>.
-- 
2.35.3

openSUSE Build Service is sponsored by