29
29
equality /1 ,ordering /1 ,
30
30
fun_to_port /1 ,t_phash /1 ,t_phash2 /1 ,md5 /1 ,
31
31
const_propagation /1 ,t_arity /1 ,t_is_function2 /1 ,
32
- t_fun_info /1 ,t_fun_info_mfa /1 ,t_fun_to_list /1 ]).
32
+ t_fun_info /1 ,t_fun_info_mfa /1 ,t_fun_to_list /1 ,
33
+ spurious_badfun /1 ]).
33
34
34
35
-export ([nothing /0 ]).
35
36
37
+ % % Callback for a process that uses this module as an error_handler module.
38
+ -export ([undefined_lambda /3 ]).
39
+
36
40
-include_lib (" common_test/include/ct.hrl" ).
37
41
38
42
suite () ->
@@ -46,7 +50,8 @@ all() ->
46
50
equality , ordering , fun_to_port , t_phash ,
47
51
t_phash2 , md5 ,
48
52
const_propagation , t_arity , t_is_function2 , t_fun_info ,
49
- t_fun_info_mfa ,t_fun_to_list ].
53
+ t_fun_info_mfa ,t_fun_to_list ,
54
+ spurious_badfun ].
50
55
51
56
init_per_testcase (_TestCase , Config ) ->
52
57
Config .
@@ -743,6 +748,73 @@ verify_not_undef(Fun, Tag) ->
743
748
{Tag ,_ } -> ok
744
749
end .
745
750
751
+ % % Test for a race condition that occurred when multiple processes
752
+ % % attempted to a call a fun whose defining module was not loaded.
753
+ spurious_badfun (Config ) ->
754
+ Mod = ? FUNCTION_NAME ,
755
+ Dir = proplists :get_value (priv_dir , Config ),
756
+ File = filename :join (Dir , atom_to_list (Mod ) ++ " .erl" ),
757
+
758
+ Code = ~ """
759
+ -module(spurious_badfun).
760
+ -export([factory/0]).
761
+ factory() ->
762
+ fun() -> ok end.
763
+ """ ,
764
+
765
+ ok = file :write_file (File , Code ),
766
+
767
+ {ok ,Mod ,Bin } = compile :file (File , [binary ]),
768
+ {module ,Mod } = erlang :load_module (Mod , Bin ),
769
+ Fun = Mod :factory (),
770
+
771
+ do_spurious_badfun (1000 , Mod , Bin , Fun ).
772
+
773
+ do_spurious_badfun (0 , _Mod , _Bin , _Fun ) ->
774
+ ok ;
775
+ do_spurious_badfun (N , Mod , Bin , Fun ) ->
776
+ _ = catch erlang :purge_module (Mod ),
777
+ _ = erlang :delete_module (Mod ),
778
+ _ = catch erlang :purge_module (Mod ),
779
+
780
+ Prepared = erlang :prepare_loading (Mod , Bin ),
781
+
782
+ {Pid ,Ref } = spawn_monitor (fun () -> call_fun (Fun ) end ),
783
+
784
+ ok = erlang :finish_loading ([Prepared ]),
785
+
786
+ receive
787
+ {'DOWN' ,Ref ,process ,Pid ,Result } ->
788
+ normal = Result ,
789
+ do_spurious_badfun (N - 1 , Mod , Bin , Fun )
790
+ end .
791
+
792
+ call_fun (Fun ) ->
793
+ % % Set up the current module as the error_handler for the current
794
+ % % process.
795
+ process_flag (error_handler , ? MODULE ),
796
+
797
+ % % With the JIT, the following call would sometimes fail with a
798
+ % % `badfun` exeception. The reason is that the native code and the
799
+ % % C function beam_jit_handle_unloaded_fun() handling an unloaded
800
+ % % fun would use different code indexes. The native code would
801
+ % % "think" that the module for the fun was not loaded, while
802
+ % % beam_jit_handle_unloaded_fun() function would "think" that the
803
+ % % module was loaded and raise a badfun exception.
804
+ Fun ().
805
+
806
+ % % This is the error_handler callback for the process that is calling
807
+ % % the fun.
808
+ undefined_lambda (_Module , Fun , Args ) ->
809
+ % % If the parent process has finished loading the module, the
810
+ % % following apply/2 call will succeed. Otherwise, this function
811
+ % % will be called again.
812
+ apply (Fun , Args ).
813
+
814
+ % %%
815
+ % %% Common utilities.
816
+ % %%
817
+
746
818
id (X ) ->
747
819
X .
748
820
0 commit comments