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