File 3515-compiler-Introduce-opaque-expressions-in-core-langua.patch of Package erlang

From f30cc9ab5cc9fddb60152233847e4f356c3d0e0c Mon Sep 17 00:00:00 2001
From: Frej Drejhammar <frej.drejhammar@gmail.com>
Date: Wed, 30 Nov 2022 13:23:18 +0100
Subject: [PATCH 05/13] compiler: Introduce opaque expressions in core language

Introduce an opaque expression which is intended to pass a term
unchanged through the passes which are run on the core representation.
---
 lib/compiler/src/cerl.erl          |  7 +++++--
 lib/compiler/src/cerl_trees.erl    | 25 +++++++++++++++++++------
 lib/compiler/src/core_parse.hrl    |  2 ++
 lib/compiler/src/core_pp.erl       |  4 +++-
 lib/compiler/src/sys_core_fold.erl |  4 +++-
 lib/compiler/src/v3_core.erl       |  9 ++++++++-
 6 files changed, 40 insertions(+), 11 deletions(-)

diff --git a/lib/compiler/src/cerl.erl b/lib/compiler/src/cerl.erl
index 99651ebc2f..00081ff594 100644
--- a/lib/compiler/src/cerl.erl
+++ b/lib/compiler/src/cerl.erl
@@ -156,6 +156,7 @@
 -type c_map()     :: #c_map{}.
 -type c_map_pair() :: #c_map_pair{}.
 -type c_module()  :: #c_module{}.
+-type c_opaque()  :: #c_opaque{}.
 -type c_primop()  :: #c_primop{}.
 -type c_receive() :: #c_receive{}.
 -type c_seq()     :: #c_seq{}.
@@ -168,7 +169,8 @@
               | c_call()   | c_case()   | c_catch()   | c_clause()  | c_cons()
               | c_fun()    | c_let()    | c_letrec()  | c_literal()
 	      | c_map()    | c_map_pair()
-	      | c_module() | c_primop() | c_receive() | c_seq()
+	      | c_module() | c_opaque()
+              | c_primop() | c_receive() | c_seq()
               | c_try()    | c_tuple()  | c_values()  | c_var().
 
 -type var_name() :: integer() | atom() | {atom(), integer()}.
@@ -292,7 +294,8 @@ type(#c_seq{}) -> seq;
 type(#c_try{}) -> 'try';
 type(#c_tuple{}) -> tuple;
 type(#c_values{}) -> values;
-type(#c_var{}) -> var.
+type(#c_var{}) -> var;
+type(#c_opaque{}) -> opaque.
 
 
 %% @spec is_leaf(Node::cerl()) -> boolean()
diff --git a/lib/compiler/src/cerl_trees.erl b/lib/compiler/src/cerl_trees.erl
index 383d9b5214..58863b24f9 100644
--- a/lib/compiler/src/cerl_trees.erl
+++ b/lib/compiler/src/cerl_trees.erl
@@ -198,7 +198,9 @@ map_1(F, T) ->
 	    update_c_module(T, map(F, module_name(T)),
 			    map_list(F, module_exports(T)),
 			    map_pairs(F, module_attrs(T)),
-			    map_pairs(F, module_defs(T)))
+			    map_pairs(F, module_defs(T)));
+        opaque ->
+            T
     end.
 
 map_list(F, [T | Ts]) ->
@@ -312,7 +314,9 @@ fold_1(F, S, T) ->
 					    fold(F, S, module_name(T)),
 					    module_exports(T)),
 				  module_attrs(T)),
-		       module_defs(T))
+		       module_defs(T));
+        opaque ->
+            S
     end.
 
 fold_list(F, S, [T | Ts]) ->
@@ -483,7 +487,9 @@ mapfold(Pre, Post, S00, T0) ->
 		    {Es, S2} = mapfold_list(Pre, Post, S1, module_exports(T)),
 		    {As, S3} = mapfold_pairs(Pre, Post, S2, module_attrs(T)),
 		    {Ds, S4} = mapfold_pairs(Pre, Post, S3, module_defs(T)),
-		    Post(update_c_module(T, N, Es, As, Ds), S4)
+		    Post(update_c_module(T, N, Es, As, Ds), S4);
+                opaque ->
+                    Post(T, S0)
 	    end;
 	skip ->
 	    {T0, S00}
@@ -657,7 +663,9 @@ variables(T, S) ->
 		    ordsets:subtract(Vs1, Vs2);
 		false ->
 		    ordsets:union(Vs1, Vs2)
-	    end
+	    end;
+        opaque ->
+            []
     end.
 
 vars_in_list(Ts, S) ->
@@ -782,7 +790,9 @@ next_free(T, Max) ->
             Max2 = next_free(letrec_body(T), Max1),
             next_free_in_list(letrec_vars(T), Max2);
         module ->
-            next_free_in_defs(module_defs(T), Max)
+            next_free_in_defs(module_defs(T), Max);
+        opaque ->
+            Max
     end.
 
 next_free_in_list([H | T], Max) ->
@@ -974,7 +984,10 @@ label(T, N, Env) ->
 	    {Ds, N3} = label_defs(module_defs(T), N2, Env1),
 	    {Es, N4} = label_list(module_exports(T), N3, Env1),
 	    {As, N5} = label_ann(T, N4),
-	    {ann_c_module(As, module_name(T), Es, Ts, Ds), N5}
+	    {ann_c_module(As, module_name(T), Es, Ts, Ds), N5};
+        opaque ->
+	    %% Not labeled.
+	    {T, N}
     end.
 
 label_list([T | Ts], N, Env) ->
diff --git a/lib/compiler/src/core_parse.hrl b/lib/compiler/src/core_parse.hrl
index 90c796d3d9..600050191a 100644
--- a/lib/compiler/src/core_parse.hrl
+++ b/lib/compiler/src/core_parse.hrl
@@ -87,6 +87,8 @@
 		   attrs :: [{cerl:cerl(), cerl:cerl()}],
 		   defs :: [{cerl:cerl(), cerl:cerl()}]}).
 
+-record(c_opaque, {anno=[] :: list(), val :: any()}).
+
 -record(c_primop, {anno=[] :: list(), name :: cerl:cerl(),
 		   args :: [cerl:cerl()]}).
 
diff --git a/lib/compiler/src/core_pp.erl b/lib/compiler/src/core_pp.erl
index 65ba7cde00..c86de6499f 100644
--- a/lib/compiler/src/core_pp.erl
+++ b/lib/compiler/src/core_pp.erl
@@ -359,7 +359,9 @@ format_1(#c_module{name=N,exports=Es,attrs=As,defs=Ds}, Ctxt) ->
      format_funcs(Ds, Ctxt),
      nl_indent(Ctxt)
      | "end"
-    ].
+    ];
+format_1(#c_opaque{val=V}, Ctxt) ->
+    ["%% Opaque: ", format_1(#c_literal{val=V}, Ctxt)].
 
 format_funcs(Fs, Ctxt) ->
     format_vseq(Fs,
diff --git a/lib/compiler/src/sys_core_fold.erl b/lib/compiler/src/sys_core_fold.erl
index d343023365..6a4b86bb0c 100644
--- a/lib/compiler/src/sys_core_fold.erl
+++ b/lib/compiler/src/sys_core_fold.erl
@@ -403,7 +403,9 @@ expr(#c_try{anno=A,arg=E0,vars=Vs0,body=B0,evars=Evs0,handler=H0}=Try, _, Sub0)
 	    {Evs1,Sub2} = var_list(Evs0, Sub0),
 	    H1 = body(H0, value, Sub2),
 	    Try#c_try{arg=E1,vars=Vs1,body=B1,evars=Evs1,handler=H1}
-    end.
+    end;
+expr(#c_opaque{}=O, effect, _Sub) ->
+    O.
 
 %% If a fun or its application is used as an argument, then it's unsafe to
 %% handle it in effect context as the side-effects may rely on its return
diff --git a/lib/compiler/src/v3_core.erl b/lib/compiler/src/v3_core.erl
index be7c8e3590..8dccc52ba6 100644
--- a/lib/compiler/src/v3_core.erl
+++ b/lib/compiler/src/v3_core.erl
@@ -975,7 +975,9 @@ expr({op,L,Op,L0,R0}, St0) ->
     LineAnno = full_anno(L, St1),
     {#icall{anno=#a{anno=LineAnno},		%Must have an #a{}
 	    module=#c_literal{anno=LineAnno,val=erlang},
-	    name=#c_literal{anno=LineAnno,val=Op},args=As},Aps,St1}.
+	    name=#c_literal{anno=LineAnno,val=Op},args=As},Aps,St1};
+expr({ssa_check_when,L,WantedResult,Args,Tag,Clauses}, St) ->
+    {#c_opaque{anno=full_anno(L, St),val={ssa_check_when,WantedResult,Tag,Args,Clauses}}, [], St}.
 
 blockify(L0, {sequential_match,_L1,First,Then}, E) ->
     [{single_match,L0,First,E}|blockify(L0, Then, E)];
@@ -2837,6 +2839,8 @@ uexpr(#ibinary{anno=A,segments=Ss}, _, St) ->
 uexpr(#c_literal{}=Lit, _, St) ->
     Anno = get_anno(Lit),
     {set_anno(Lit, #a{us=[],anno=Anno}),St};
+uexpr(#c_opaque{}=Opaque, _, St) ->
+    {set_anno(Opaque, #a{us=[],anno=get_anno(Opaque)}),St};
 uexpr(Simple, _, St) ->
     true = is_simple(Simple),			%Sanity check!
     Vs = lit_vars(Simple),
@@ -3317,6 +3321,8 @@ cexpr(#icall{anno=A,module=Mod,name=Name,args=Args}, _As, St0) ->
 	false ->
 	    {#c_call{anno=Anno,module=Mod,name=Name,args=Args},[],A#a.us,St0}
     end;
+cexpr(O=#c_opaque{}, _As, St) ->
+    {O,[],[],St};
 cexpr(#iprimop{anno=A,name=Name,args=Args}, _As, St) ->
     {#c_primop{anno=A#a.anno,name=Name,args=Args},[],A#a.us,St};
 cexpr(#iprotect{anno=A,body=Es}, _As, St0) ->
@@ -3418,6 +3424,7 @@ skip_lowering(#c_call{}, _A) -> skip;
 skip_lowering(#c_cons{}, _A) -> skip;
 skip_lowering(#c_literal{}, _A) -> skip;
 skip_lowering(#c_map{}, _A) -> skip;
+skip_lowering(#c_opaque{}, _A) -> skip;
 skip_lowering(#c_primop{}, _A) -> skip;
 skip_lowering(#c_tuple{}, _A) -> skip;
 skip_lowering(T, A) -> {T, A}.
-- 
2.35.3

openSUSE Build Service is sponsored by