1%%
2%% %CopyrightBegin%
3%%
4%% Copyright Ericsson AB 2003-2020. All Rights Reserved.
5%%
6%% Licensed under the Apache License, Version 2.0 (the "License");
7%% you may not use this file except in compliance with the License.
8%% You may obtain a copy of the License at
9%%
10%%     http://www.apache.org/licenses/LICENSE-2.0
11%%
12%% Unless required by applicable law or agreed to in writing, software
13%% distributed under the License is distributed on an "AS IS" BASIS,
14%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
15%% See the License for the specific language governing permissions and
16%% limitations under the License.
17%%
18%% %CopyrightEnd%
19%%
20-module(ms_transform_SUITE).
21-author('pan@erix.ericsson.se').
22
23-include_lib("common_test/include/ct.hrl").
24
25-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1,
26	 init_per_testcase/2, end_per_testcase/2,
27	 init_per_group/2,end_per_group/2]).
28-export([basic_ets/1]).
29-export([basic_dbg/1]).
30-export([from_shell/1]).
31-export([records/1]).
32-export([record_index/1]).
33-export([multipass/1]).
34-export([top_match/1]).
35-export([old_guards/1]).
36-export([autoimported/1]).
37-export([semicolon/1]).
38-export([bitsyntax/1]).
39-export([record_defaults/1]).
40-export([andalso_orelse/1]).
41-export([float_1_function/1]).
42-export([action_function/1]).
43-export([warnings/1]).
44-export([no_warnings/1]).
45-export([eep37/1]).
46-export([otp_14454/1]).
47
48init_per_testcase(_Func, Config) ->
49    Config.
50
51end_per_testcase(_Func, _Config) ->
52    ok.
53
54suite() ->
55    [{ct_hooks,[ts_install_cth]},
56     {timetrap,{minutes,6}}].
57
58all() ->
59    [from_shell, basic_ets, basic_dbg, records,
60     record_index, multipass, bitsyntax, record_defaults,
61     andalso_orelse, float_1_function, action_function,
62     warnings, no_warnings, top_match, old_guards, autoimported,
63     semicolon, eep37, otp_14454].
64
65groups() ->
66    [].
67
68init_per_suite(Config) ->
69    Config.
70
71end_per_suite(_Config) ->
72    ok.
73
74init_per_group(_GroupName, Config) ->
75    Config.
76
77end_per_group(_GroupName, Config) ->
78    Config.
79
80
81%% This may be subject to change
82-define(WARN_NUMBER_SHADOW,50).
83
84%% Check that shadowed variables in fun head generate warning.
85warnings(Config) when is_list(Config) ->
86    setup(Config),
87    Prog = <<"A=5, "
88	     "ets:fun2ms(fun({A,B}) "
89	     "            when is_integer(A) and (A+5 > B) -> "
90	     "              A andalso B "
91	     "            end)">>,
92    [{_,[{_,ms_transform,{?WARN_NUMBER_SHADOW,'A'}}]}] =
93	compile_ww(Prog),
94    Prog2 = <<"C = 5,
95               ets:fun2ms(fun ({A,B} =
96				   C) when is_integer(A) and (A+5 > B) ->
97                                  {A andalso B,C}
98                          end)">>,
99    [{_,[{3,ms_transform,{?WARN_NUMBER_SHADOW,'C'}}]}] =
100	      compile_ww(Prog2),
101	      Rec3 = <<"-record(a,{a,b,c,d=foppa}).">>,
102	      Prog3 = <<"A = 3,
103               C = 5,
104			ets:fun2ms(fun (C
105					= #a{a = A, b = B})
106					 when is_integer(A) and (A+5 > B) ->
107					   {A andalso B,C}
108				   end)">>,
109    [{_,[{3,ms_transform,{?WARN_NUMBER_SHADOW,'C'}},
110         {4,ms_transform,{?WARN_NUMBER_SHADOW,'A'}}]}] =
111			compile_ww(Rec3,Prog3),
112			Rec4 = <<"-record(a,{a,b,c,d=foppa}).">>,
113			Prog4 = <<"A=3,C=5, "
114				  "F = fun(B) -> B*3 end,"
115				  "erlang:display(F(A)),"
116				  "ets:fun2ms(fun(#a{a = A, b = B} = C) "
117				  "            when is_integer(A) and (A+5 > B) -> "
118				  "              {A andalso B,C} "
119				  "            end)">>,
120			[{_,[{_,ms_transform,{?WARN_NUMBER_SHADOW,'A'}},
121			     {_,ms_transform,{?WARN_NUMBER_SHADOW,'C'}}]}] =
122			compile_ww(Rec4,Prog4),
123			Rec5 = <<"-record(a,{a,b,c,d=foppa}).">>,
124			Prog5 = <<"A=3,C=5, "
125				  "F = fun(B) -> B*3 end,"
126				  "erlang:display(F(A)),"
127				  "B = ets:fun2ms(fun(#a{a = A, b = B} = C) "
128				  "            when is_integer(A) and (A+5 > B) -> "
129				  "              {A andalso B,C} "
130				  "            end)">>,
131			[{_,[{_,ms_transform,{?WARN_NUMBER_SHADOW,'A'}},
132			     {_,ms_transform,{?WARN_NUMBER_SHADOW,'C'}}]}] =
133			compile_ww(Rec5,Prog5),
134			Prog6 = <<"   X=bar, "
135				  "    A = case X of"
136				  "       foo ->"
137				  "          foo;"
138				  "       Y ->"
139				  "          ets:fun2ms(fun(Y) ->" % This is a warning
140				  "                         3*Y"
141				  "                     end)"
142				  "   end,"
143				  "   ets:fun2ms(fun(Y) ->" % Y out of "scope" here, so no warning
144				  "                  {3*Y,A}"
145				  "              end)">>,
146			[{_,[{_,ms_transform,{?WARN_NUMBER_SHADOW,'Y'}}]}] =
147			compile_ww(Prog6),
148			Prog7 = <<"   X=bar, "
149				  "    A = case X of"
150				  "       foo ->"
151				  "          Y = foo;"
152				  "       Y ->"
153				  "          bar"
154				  "   end,"
155				  "   ets:fun2ms(fun(Y) ->" % Y exported from case and safe, so warn
156				  "                  {3*Y,A}"
157				  "              end)">>,
158			[{_,[{_,ms_transform,{?WARN_NUMBER_SHADOW,'Y'}}]}] =
159			compile_ww(Prog7),
160			ok.
161
162%% Check that variables bound in other function clauses don't generate
163%% warning.
164no_warnings(Config) when is_list(Config) ->
165    setup(Config),
166    Prog = <<"tmp(X) when X > 100 ->\n",
167	     "   Y=X,\n"
168	     "   Y;\n"
169	     "tmp(X) ->\n"
170	     "   ets:fun2ms(fun(Y) ->\n"
171	     "                  {X, 3*Y}\n"
172	     "              end)">>,
173    [] = compile_no_ww(Prog),
174
175    Prog2 = <<"tmp(X) when X > 100 ->\n",
176	      "   Y=X,\n"
177	      "   Y;\n"
178	      "tmp(X) when X < 200 ->\n"
179	      "   ok;\n"
180	      "tmp(X) ->\n"
181	      "   ets:fun2ms(fun(Y) ->\n"
182	      "                  {X, 3*Y}\n"
183	      "              end)">>,
184    [] = compile_no_ww(Prog2),
185    ok.
186
187%% Test that andalso and orelse are allowed in guards.
188andalso_orelse(Config) when is_list(Config) ->
189    setup(Config),
190    [{{'$1','$2'},
191      [{'and',{is_integer,'$1'},{'>',{'+','$1',5},'$2'}}],
192      [{'andalso','$1','$2'}]}] =
193	compile_and_run(<<"ets:fun2ms(fun({A,B}) "
194			  "            when is_integer(A) and (A+5 > B) -> "
195			  "              A andalso B "
196			  "            end)">>),
197    [{{'$1','$2'},
198      [{'or',{is_atom,'$1'},{'>',{'+','$1',5},'$2'}}],
199      [{'orelse','$1','$2'}]}] =
200	compile_and_run(<<"ets:fun2ms(fun({A,B}) "
201			  "            when is_atom(A) or (A+5 > B) -> "
202			  "              A orelse B "
203			  "            end)">>),
204    [{{'$1','$2'},
205      [{'andalso',{is_integer,'$1'},{'>',{'+','$1',5},'$2'}}],
206      ['$1']}] =
207        compile_and_run(
208	  <<"ets:fun2ms(fun({A,B}) when is_integer(A) andalso (A+5 > B) ->"
209	    "			 A "
210	    "		 end)">>),
211    [{{'$1','$2'},
212      [{'orelse',{is_atom,'$1'},{'>',{'+','$1',5},'$2'}}],
213      ['$1']}] =
214        compile_and_run(
215	  <<"ets:fun2ms(fun({A,B}) when is_atom(A) orelse (A+5 > B) -> "
216	    "			 A "
217	    "		 end)">>),
218    ok.
219
220
221%% Test that bitsyntax works and does not work where appropriate.
222bitsyntax(Config) when is_list(Config) ->
223    setup(Config),
224    [{'_',[],
225      [<<0,27,0,27>>]}] =
226	compile_and_run(<<"A = 27, "
227			  "ets:fun2ms(fun(_) -> <<A:16,27:16>> end)">>),
228    [{{<<15,47>>,
229       '$1',
230       '$2'},
231      [{'=:=','$1',
232	<<0,27>>},
233       {'=:=','$2',
234	<<27,28,19>>}],
235      [<<188,0,13>>]}] =
236	compile_and_run(<<"A = 27, "
237			  "ets:fun2ms("
238                          "  fun({<<15,47>>,B,C}) "
239			  "  when B =:= <<A:16>>, C =:= <<27,28,19>> -> "
240			  "    <<A:4,12:4,13:16>> "
241			  "  end)">>),
242    expect_failure(
243      <<>>,
244      <<"ets:fun2ms(fun({<<15,47>>,B,C}) "
245	"            when B =:= <<16>>, C =:= <<27,28,19>> -> "
246	"              <<B:4,12:4,13:16>> "
247	"            end)">>),
248    expect_failure(
249      <<>>,
250      <<"ets:fun2ms(fun({<<A:15,47>>,B,C}) "
251	"            when B =:= <<16>>, C =:= <<27,28,19>> -> "
252	"              <<B:4,12:4,13:16>> "
253	"            end)">>),
254    ok.
255
256%% Test that record defaults works.
257record_defaults(Config) when is_list(Config) ->
258    setup(Config),
259    [{{<<27>>,{a,5,'$1',hej,hej}},
260      [],
261      [{{a,hej,{'*','$1',2},flurp,flurp}}]}] =
262	compile_and_run(<<"-record(a,{a,b,c,d=foppa}).">>,
263			<<"ets:fun2ms(fun({<<27>>,#a{a=5, b=B,_=hej}}) -> "
264			  "#a{a=hej,b=B*2,_=flurp} "
265			  "end)">>),
266    ok.
267
268%% Test basic ets:fun2ms.
269basic_ets(Config) when is_list(Config) ->
270    setup(Config),
271    [{{a,b},[],[true]}] = compile_and_run(
272			    <<"ets:fun2ms(fun({a,b}) -> true end)">>),
273    [{{'$1',foo},[{is_list,'$1'}],[{{{hd,'$1'},'$_'}}]},
274     {{'$1','$1'},[{is_tuple,'$1'}],[{{{element,1,'$1'},'$*'}}]}] =
275	compile_and_run(<<"ets:fun2ms(fun({X,foo}) when is_list(X) -> ",
276			  "{hd(X),object()};",
277			  "({X,X}) when is_tuple(X) ->",
278			  "{element(1,X),bindings()}",
279			  "end)">>),
280    [{{'$1','$2'},[],[{{'$2','$1'}}]}] =
281	compile_and_run(<<"ets:fun2ms(fun({A,B}) -> {B,A} end)">>),
282    [{{'$1','$2'},[],[['$2','$1']]}] =
283	compile_and_run(<<"ets:fun2ms(fun({A,B}) -> [B,A] end)">>),
284    [{{"foo" ++ '_','$1'},[],['$1']}] =
285        compile_and_run(<<"ets:fun2ms(fun({\"foo\" ++ _, X}) -> X end)">>),
286    ok.
287
288%% Tests basic ets:fun2ms.
289basic_dbg(Config) when is_list(Config) ->
290    setup(Config),
291    [{[a,b],[],[{message,banan},{return_trace}]}] =
292	compile_and_run(<<"dbg:fun2ms(fun([a,b]) -> message(banan), ",
293			  "return_trace() end)">>),
294    [{['$1','$2'],[],[{{'$2','$1'}}]}] =
295	compile_and_run(<<"dbg:fun2ms(fun([A,B]) -> {B,A} end)">>),
296    [{['$1','$2'],[],[['$2','$1']]}] =
297	compile_and_run(<<"dbg:fun2ms(fun([A,B]) -> [B,A] end)">>),
298    [{['$1','$2'],[],['$*']}] =
299	compile_and_run(<<"dbg:fun2ms(fun([A,B]) -> bindings() end)">>),
300    [{['$1','$2'],[],['$_']}] =
301	compile_and_run(<<"dbg:fun2ms(fun([A,B]) -> object() end)">>),
302    [{[],[],[{return_trace}]}] =
303	compile_and_run(<<"dbg:fun2ms(fun([]) -> return_trace() end)">>),
304    ok.
305
306%% Test calling of ets/dbg:fun2ms from the shell.
307from_shell(Config) when is_list(Config) ->
308    setup(Config),
309    Fun = do_eval("fun({a,b}) -> true end"),
310    [{{a,b},[],[true]}] = apply(ets,fun2ms,[Fun]),
311    [{{a,b},[],[true]}] = do_eval("ets:fun2ms(fun({a,b}) -> true end)"),
312    Fun2 = do_eval("fun([a,b]) -> message(banan), return_trace() end"),
313    [{[a,b],[],[{message,banan},{return_trace}]}]
314	= apply(dbg,fun2ms,[Fun2]),
315    [{[a,b],[],[{message,banan},{return_trace}]}] =
316	do_eval(
317	  "dbg:fun2ms(fun([a,b]) -> message(banan), return_trace() end)"),
318    [{{"foo" ++ '_','$1'},[],['$1']}] =
319        do_eval("ets:fun2ms(fun({\"foo\" ++ _, X}) -> X end)"),
320    ok.
321
322%% Tests expansion of records in fun2ms.
323records(Config) when is_list(Config) ->
324    setup(Config),
325    RD = <<"-record(t, {"
326	   "t1 = [] :: list(),"
327	   "t2 = foo :: atom(),"
328	   "t3,"
329	   "t4"
330	   "}).">>,
331    [{{t,'$1','$2',foo,'_'},[{is_list,'$1'}],[{{{hd,'$1'},'$_'}}]},
332     {{t,'_','_','_','_'},[{'==',{element,2,'$_'},nisse}],[{{'$*'}}]}] =
333	compile_and_run(RD,<<
334			     "ets:fun2ms(fun(#t{t1 = X, t2 = Y, t3 = foo}) when is_list(X) ->
335 		       {hd(X),object()};
336			     (#t{}) when (object())#t.t1 == nisse ->
337				   {bindings()}
338			   end)">>),
339    [{{t,'$1','$2','_',foo},
340      [{'==',{element,4,'$_'},7},{is_list,'$1'}],
341      [{{{hd,'$1'},'$_'}}]},
342     {'$1',[{is_record,'$1',t,5}],
343      [{{{element,2,'$1'},
344	 {{t,'$1',foo,undefined,undefined}},
345	 {{t,{element,2,'$1'},{element,3,'$1'},{element,4,'$1'},boooo}}}}]}] =
346	compile_and_run(RD,<<
347    "ets:fun2ms(fun(#t{t1 = X, t2 = Y, t4 = foo}) when
348			 (object())#t.t3==7,is_list(X) ->
349 		       {hd(X),object()};
350 		  (A) when is_record(A,t) ->
351 		       {A#t.t1
352			,#t{t1=A}
353			,A#t{t4=boooo}
354		       }
355 	       end)"
356			>>),
357    [{[{t,'$1','$2',foo,'_'}],[{is_list,'$1'}],[{{{hd,'$1'},'$_'}}]},
358     {[{t,'_','_','_','_'}],[{'==',{element,2,{hd,'$_'}},nisse}],[{{'$*'}}]}]=
359	compile_and_run(RD,<<
360    "dbg:fun2ms(fun([#t{t1 = X, t2 = Y, t3 = foo}]) when is_list(X) ->
361 		       {hd(X),object()};
362 		  ([#t{}]) when (hd(object()))#t.t1 == nisse ->
363 		       {bindings()}
364 	       end)"
365			>>),
366    ok.
367
368
369%% Test expansion of records in fun2ms, part 2.
370record_index(Config) when is_list(Config) ->
371    setup(Config),
372    RD = <<"-record(a,{a,b}).">>,
373    [{{2},[],[true]}] = compile_and_run(RD,
374			  <<"ets:fun2ms(fun({#a.a}) -> true end)">>),
375    [{{2},[],[2]}] = compile_and_run(RD,
376			  <<"ets:fun2ms(fun({#a.a}) -> #a.a end)">>),
377    [{{2,'$1'},[{'>','$1',2}],[2]}] = compile_and_run(RD,
378		    <<"ets:fun2ms(fun({#a.a,A}) when A > #a.a -> #a.a end)">>),
379    ok.
380
381%% Tests matching on top level in head to give alias for object().
382top_match(Config) when is_list(Config) ->
383    setup(Config),
384    RD = <<"-record(a,{a,b}).">>,
385    [{{a,3,'_'},[],['$_']}] =
386	compile_and_run(RD,
387			<<"ets:fun2ms(fun(A = #a{a=3}) -> A end)">>),
388    [{{a,3,'_'},[],['$_']}] =
389	compile_and_run(RD,
390			<<"ets:fun2ms(fun(#a{a=3} = A) -> A end)">>),
391    [{[a,b],[],['$_']}] =
392	compile_and_run(RD,
393			<<"dbg:fun2ms(fun(A = [a,b]) -> A end)">>),
394    [{[a,b],[],['$_']}] =
395	compile_and_run(RD,
396			<<"dbg:fun2ms(fun([a,b] = A) -> A end)">>),
397    expect_failure(RD,
398			 <<"ets:fun2ms(fun({a,A = {_,b}}) -> A end)">>),
399    expect_failure(RD,
400			 <<"dbg:fun2ms(fun([a,A = {_,b}]) -> A end)">>),
401    expect_failure(RD,
402			 <<"ets:fun2ms(fun(A#a{a = 2}) -> A end)">>),
403    ok.
404
405%% Tests that multi-defined fields in records give errors.
406multipass(Config) when is_list(Config) ->
407    setup(Config),
408    RD = <<"-record(a,{a,b}).">>,
409    expect_failure(RD,<<"ets:fun2ms(fun(A) -> #a{a=2,a=3} end)">>),
410    expect_failure(RD,<<"ets:fun2ms(fun(A) -> A#a{a=2,a=3} end)">>),
411    expect_failure(RD,<<"ets:fun2ms(fun(A) when A =:= #a{a=2,a=3} ->",
412			 " true end)">>),
413    expect_failure(RD,<<"ets:fun2ms(fun({A,B})when A =:= B#a{a=2,a=3}->",
414			 "true end)">>),
415    expect_failure(RD,<<"ets:fun2ms(fun(#a{a=3,a=3}) -> true end)">>),
416    compile_and_run(RD,<<"ets:fun2ms(fun(A) -> #a{a=2,b=3} end)">>),
417    compile_and_run(RD,<<"ets:fun2ms(fun(A) -> A#a{a=2,b=3} end)">>),
418    compile_and_run(RD,<<"ets:fun2ms(fun(A) when A =:= #a{a=2,b=3} ->",
419			 " true end)">>),
420    compile_and_run(RD,<<"ets:fun2ms(fun({A,B})when A=:= B#a{a=2,b=3}->",
421			 "true end)">>),
422    compile_and_run(RD,<<"ets:fun2ms(fun(#a{a=3,b=3}) -> true end)">>),
423    ok.
424
425
426%% Test that old type tests in guards are translated.
427old_guards(Config) when is_list(Config) ->
428    setup(Config),
429    Tests = [
430	     {atom,is_atom},
431	     {float,is_float},
432	     {integer,is_integer},
433	     {list,is_list},
434	     {number,is_number},
435	     {pid,is_pid},
436	     {port,is_port},
437	     {reference,is_reference},
438	     {tuple,is_tuple},
439	     {binary,is_binary},
440	     {function,is_function}],
441    lists:foreach(
442	    fun({Old,New}) ->
443		    Bin = list_to_binary([<<"ets:fun2ms(fun(X) when ">>,
444					  atom_to_list(Old),
445					  <<"(X)  -> true end)">>]),
446		    case compile_and_run(Bin) of
447			[{'$1',[{New,'$1'}],[true]}] ->
448			    ok;
449			_ ->
450			    exit({bad_result_for, binary_to_list(Bin)})
451		    end
452	    end,
453	    Tests),
454    RD = <<"-record(a,{a,b}).">>,
455    [{'$1',[{is_record,'$1',a,3}],[true]}] =
456	compile_and_run(RD,
457			<<"ets:fun2ms(fun(X) when record(X,a) -> true end)">>),
458    expect_failure
459	    (RD,
460	     <<"ets:fun2ms(fun(X) when integer(X) and constant(X) -> "
461	      "true end)">>),
462    [{'$1',[{is_integer,'$1'},
463		  {is_float,'$1'},
464		  {is_atom,'$1'},
465		  {is_list,'$1'},
466		  {is_number,'$1'},
467		  {is_pid,'$1'},
468		  {is_port,'$1'},
469		  {is_reference,'$1'},
470		  {is_tuple,'$1'},
471		  {is_binary,'$1'},
472		  {is_record,'$1',a,3}],
473	    [true]}] =
474	compile_and_run(RD, <<
475			     "ets:fun2ms(fun(X) when integer(X),"
476			     "float(X), atom(X),"
477			     "list(X), number(X), pid(X),"
478			     "port(X), reference(X), tuple(X),"
479			     "binary(X), record(X,a) -> true end)"
480			     >>),
481    ok.
482
483%% Test use of autoimported BIFs used like erlang:'+'(A,B) in guards
484%% and body.
485autoimported(Config) when is_list(Config) ->
486    setup(Config),
487    Allowed = [
488	       {abs,1},
489	       {element,2},
490	       {hd,1},
491	       {length,1},
492	       {node,0},
493	       {node,1},
494	       {round,1},
495	       {size,1},
496	       {tl,1},
497	       {trunc,1},
498	       {self,0},
499               %%{float,1}, see float_1_function/1
500	       {is_atom,1},
501	       {is_float,1},
502	       {is_integer,1},
503	       {is_list,1},
504	       {is_number,1},
505	       {is_pid,1},
506	       {is_port,1},
507	       {is_reference,1},
508	       {is_tuple,1},
509	       {is_binary,1},
510	       {is_function,1},
511	       {is_record,2,magic},
512	       {'and',2,infix},
513	       {'or',2,infix},
514	       {'xor',2,infix},
515	       {'not',1},
516	       %%{'andalso',2,infix},
517	       %%{'orelse',2,infix},
518	       {'+',1},
519	       {'+',2,infix},
520	       {'-',1},
521	       {'-',2,infix},
522	       {'*',2,infix},
523	       {'/',2,infix},
524	       {'div',2,infix},
525	       {'rem',2,infix},
526	       {'band',2,infix},
527	       {'bor',2,infix},
528	       {'bxor',2,infix},
529	       {'bnot',1},
530	       {'bsl',2,infix},
531	       {'bsr',2,infix},
532	       {'>',2,infix},
533	       {'>=',2,infix},
534	       {'<',2,infix},
535	       {'=<',2,infix},
536	       {'==',2,infix},
537	       {'=:=',2,infix},
538	       {'/=',2,infix},
539	       {'=/=',2,infix}],
540    RD = <<"-record(a,{a,b}).">>,
541    lists:foreach(
542	    fun({A,0}) ->
543		    L = atom_to_list(A),
544		    Bin1 = list_to_binary(
545			     [
546			      <<"ets:fun2ms(fun(X) when ">>,
547			      L,<<"() -> ">>,
548			      L,<<"() end)">>
549			     ]),
550		    Bin2 = list_to_binary(
551			     [
552			      <<"ets:fun2ms(fun(X) when erlang:'">>,
553			      L,<<"'() -> erlang:'">>,
554			      L,<<"'() end)">>
555			     ]),
556		    Res1 = compile_and_run(Bin1),
557		    Res2 = compile_and_run(Bin2),
558		    case Res1 =:= Res2 of
559			true ->
560			    ok;
561			false ->
562			    exit({not_equal,{Res1,Res2,A}})
563		    end;
564	    ({A,1}) ->
565		    L = atom_to_list(A),
566		    Bin1 = list_to_binary(
567			     [
568			      <<"ets:fun2ms(fun(X) when ">>,
569			      L,<<"(X) -> ">>,
570			      L,<<"(X) end)">>
571			     ]),
572		    Bin2 = list_to_binary(
573			     [
574			      <<"ets:fun2ms(fun(X) when erlang:'">>,
575			      L,<<"'(X) -> erlang:'">>,
576			      L,<<"'(X) end)">>
577			     ]),
578		    Res1 = compile_and_run(Bin1),
579		    Res2 = compile_and_run(Bin2),
580		    case Res1 =:= Res2 of
581			true ->
582			    ok;
583			false ->
584			    exit({not_equal,{Res1,Res2,A}})
585		    end;
586	    ({A,2}) ->
587		    L = atom_to_list(A),
588		    Bin1 = list_to_binary(
589			     [
590			      <<"ets:fun2ms(fun({X,Y}) when ">>,
591			      L,<<"(X,Y) -> ">>,
592			      L,<<"(X,Y) end)">>
593			     ]),
594		    Bin2 = list_to_binary(
595			     [
596			      <<"ets:fun2ms(fun({X,Y}) when erlang:'">>,
597			      L,<<"'(X,Y) -> erlang:'">>,
598			      L,<<"'(X,Y) end)">>
599			     ]),
600		    Res1 = compile_and_run(Bin1),
601		    Res2 = compile_and_run(Bin2),
602		    case Res1 =:= Res2 of
603			true ->
604			    ok;
605			false ->
606			    exit({not_equal,{Res1,Res2,A}})
607		    end;
608	    ({A,2,infix}) ->
609		    L = atom_to_list(A),
610		    Bin1 = list_to_binary(
611			     [
612			      <<"ets:fun2ms(fun({X,Y}) when X ">>,
613			      L,<<" Y -> X ">>,
614			      L,<<" Y end)">>
615			     ]),
616		    Bin2 = list_to_binary(
617			     [
618			      <<"ets:fun2ms(fun({X,Y}) when erlang:'">>,
619			      L,<<"'(X,Y) -> erlang:'">>,
620			      L,<<"'(X,Y) end)">>
621			     ]),
622		    Res1 = compile_and_run(Bin1),
623		    Res2 = compile_and_run(Bin2),
624		    case Res1 =:= Res2 of
625			true ->
626			    ok;
627			false ->
628			    exit({not_equal,{Res1,Res2,A}})
629		    end;
630	    ({A,2,magic}) -> %is_record
631		    L = atom_to_list(A),
632		    Bin1 = list_to_binary(
633			     [
634			      <<"ets:fun2ms(fun(X) when ">>,
635			      L,<<"(X,a) -> ">>,
636			      L,<<"(X,a) end)">>
637			     ]),
638		    Bin2 = list_to_binary(
639			     [
640			      <<"ets:fun2ms(fun(X) when erlang:'">>,
641			      L,<<"'(X,a) -> erlang:'">>,
642			      L,<<"'(X,a) end)">>
643			     ]),
644		    Res1 = compile_and_run(RD,Bin1),
645		    Res2 = compile_and_run(RD,Bin2),
646		    case Res1 =:= Res2 of
647			true ->
648			    ok;
649			false ->
650			    exit({not_equal,{Res1,Res2,A}})
651		    end
652	    end,
653	    Allowed),
654    ok.
655
656%% Test semicolon in guards of match_specs.
657semicolon(Config) when is_list(Config) ->
658    setup(Config),
659    Res01 = compile_and_run
660		   (<<"ets:fun2ms(fun(X) when is_integer(X); "
661		     "is_float(X) -> true end)">>),
662    Res02 = compile_and_run
663		   (<<"ets:fun2ms(fun(X) when is_integer(X) -> true; "
664		     "(X) when is_float(X) -> true end)">>),
665    Res01 = Res02,
666    Res11 = compile_and_run
667		   (<<"ets:fun2ms(fun(X) when is_integer(X); "
668		     "is_float(X); atom(X) -> true end)">>),
669    Res12 = compile_and_run
670		   (<<"ets:fun2ms(fun(X) when is_integer(X) -> true; "
671		     "(X) when is_float(X) -> true; "
672		     "(X) when is_atom(X) -> true end)">>),
673    Res11 = Res12,
674    ok.
675
676
677%% OTP-5297. The function float/1.
678float_1_function(Config) when is_list(Config) ->
679    setup(Config),
680    RunMS = fun(L, MS) ->
681                    ets:match_spec_run(L, ets:match_spec_compile(MS))
682            end,
683    MS1 = compile_and_run
684                  (<<"ets:fun2ms(fun(X) -> float(X) end)">>),
685    [F1] = RunMS([3], MS1),
686    true = is_float(F1) and (F1 == 3),
687
688    MS1b = compile_and_run
689                  (<<"dbg:fun2ms(fun(X) -> float(X) end)">>),
690    [F2] = RunMS([3], MS1b),
691    true = is_float(F2) and (F2 == 3),
692
693    MS2 = compile_and_run
694            (<<"ets:fun2ms(fun(X) when is_pid(X) or float(X) -> true end)">>),
695    [] = RunMS([3.0], MS2),
696
697    MS3 = compile_and_run
698            (<<"dbg:fun2ms(fun(X) when is_pid(X); float(X) -> true end)">>),
699    [true] = RunMS([3.0], MS3),
700
701    MS4 = compile_and_run
702            (<<"ets:fun2ms(fun(X) when erlang:float(X) > 1 -> big;"
703               "              (_) -> small end)">>),
704    [small,big] = RunMS([1.0, 3.0], MS4),
705
706    MS5 = compile_and_run
707            (<<"ets:fun2ms(fun(X) when float(X) > 1 -> big;"
708               "              (_) -> small end)">>),
709    [small,big] = RunMS([1.0, 3.0], MS5),
710
711    %% This is the test from autoimported/1.
712    [{'$1',[{is_float,'$1'}],[{float,'$1'}]}] =
713        compile_and_run
714            (<<"ets:fun2ms(fun(X) when float(X) -> float(X) end)">>),
715    [{'$1',[{float,'$1'}],[{float,'$1'}]}] =
716        compile_and_run
717           (<<"ets:fun2ms(fun(X) when erlang:'float'(X) -> "
718              "erlang:'float'(X) end)">>),
719    ok.
720
721
722%% Test all 'action functions'.
723action_function(Config) when is_list(Config) ->
724    setup(Config),
725    [{['$1','$2'],[],
726	    [{set_seq_token,label,0},
727	     {get_seq_token},
728	     {message,'$1'},
729	     {return_trace},
730	     {exception_trace}]}] =
731	compile_and_run
732	  (<<"dbg:fun2ms(fun([X,Y]) -> "
733	    "set_seq_token(label, 0), "
734	    "get_seq_token(), "
735	    "message(X), "
736	    "return_trace(), "
737	    "exception_trace() end)">>),
738    [{['$1','$2'],[],
739	    [{process_dump},
740	     {enable_trace,send},
741	     {enable_trace,'$2',send},
742	     {disable_trace,procs},
743	     {disable_trace,'$2',procs}]}] =
744	compile_and_run
745	  (<<"dbg:fun2ms(fun([X,Y]) -> "
746	    "process_dump(), "
747	    "enable_trace(send), "
748	    "enable_trace(Y, send), "
749	    "disable_trace(procs), "
750	    "disable_trace(Y, procs) end)">>),
751    [{['$1','$2'],
752	    [],
753	    [{display,'$1'},
754	     {caller},
755	     {set_tcw,{const,16}},
756	     {silent,true},
757	     {trace,[send],[procs]},
758	     {trace,'$2',[procs],[send]}]}] =
759	compile_and_run
760	  (<<"A = 16, dbg:fun2ms(fun([X,Y]) -> "
761	    "display(X), "
762	    "caller(), "
763	    "set_tcw(A), "
764	    "silent(true), "
765	    "trace([send], [procs]), "
766	    "trace(Y, [procs], [send])  end)">>),
767    ok.
768
769
770eep37(Config) when is_list(Config) ->
771    setup(Config),
772    [{'$1',[],['$1']}] =
773        compile_and_run(<<"F = fun _Ms() ->\n"
774                          "            ets:fun2ms(fun (X) -> X end)\n"
775                          "    end,\n"
776                          "F()">>).
777
778
779otp_14454(Config) when is_list(Config) ->
780    setup(Config),
781    [{'$1',[],[{'band','$1',136}]}] =
782        compile_and_run(
783          <<"ets:fun2ms(fun(A) -> A band ( -(-17) bsl 3) end)">>),
784    [{'$1',[],[{'band','$1',136}]}] =
785        compile_and_run(
786          <<"ets:fun2ms(fun(A) -> A band ( erlang:'bsl'(-(-17), 3)) end)">>),
787    ok.
788
789
790%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
791%% Helpers
792%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
793
794setup(Config) ->
795    put(mts_config,Config),
796    put(mts_tf_counter,0).
797
798temp_name() ->
799    Conf = get(mts_config),
800    C = get(mts_tf_counter),
801    put(mts_tf_counter,C+1),
802    filename:join([proplists:get_value(priv_dir,Conf),
803		   "tempfile"++integer_to_list(C)++".tmp"]).
804
805
806expect_failure(Recs,Code) ->
807    case (catch compile_and_run(Recs,Code)) of
808	      {'EXIT',_Foo} ->
809		  ok;
810	      Other ->
811		  exit({expected,failure,got,Other})
812	  end.
813
814compile_and_run(Expr) ->
815    compile_and_run(<<>>,Expr).
816compile_and_run(Records,Expr) ->
817    Prog = <<
818	"-module(tmp).\n",
819    "-include_lib(\"stdlib/include/ms_transform.hrl\").\n",
820    "-export([tmp/0]).\n",
821    Records/binary,"\n",
822    "tmp() ->\n",
823    Expr/binary,".\n">>,
824    FN=temp_name(),
825    file:write_file(FN,Prog),
826    {ok,Forms} = epp:parse_file(FN,"",""),
827    {ok,tmp,Bin} = compile:forms(Forms),
828    code:load_binary(tmp,FN,Bin),
829    tmp:tmp().
830
831compile_ww(Expr) ->
832    compile_ww(<<>>,Expr).
833compile_ww(Records,Expr) ->
834    Prog = <<
835	"-module(tmp).\n",
836    "-include_lib(\"stdlib/include/ms_transform.hrl\").\n",
837    "-export([tmp/0]).\n",
838    Records/binary,"\n",
839    "-file(?FILE, 0). ",
840    "tmp() ->\n",
841    Expr/binary,".\n">>,
842    FN=temp_name(),
843    file:write_file(FN,Prog),
844    {ok,Forms} = epp:parse_file(FN,"",""),
845    {ok,tmp,_Bin,Wlist} = compile:forms(Forms,[return_warnings,
846					       nowarn_unused_vars,
847					       nowarn_unused_record]),
848    Wlist.
849
850compile_no_ww(Expr) ->
851    Prog = <<
852	"-module(tmp).\n",
853    "-include_lib(\"stdlib/include/ms_transform.hrl\").\n",
854    "-export([tmp/1]).\n\n",
855    Expr/binary,".\n">>,
856    FN=temp_name(),
857    file:write_file(FN,Prog),
858    {ok,Forms} = epp:parse_file(FN,"",""),
859    {ok,tmp,_Bin,Wlist} = compile:forms(Forms,[return_warnings,
860					       nowarn_unused_vars,
861					       nowarn_unused_record]),
862    Wlist.
863
864do_eval(String) ->
865    {done,{ok,T,_},[]} = erl_scan:tokens(
866			   [],
867			   String++".\n",1),
868    {ok,Tree} = erl_parse:parse_exprs(T),
869    {value,Res,[]} =  erl_eval:exprs(Tree,[]),
870    Res.
871