diff options
Diffstat (limited to 'lib/compiler')
62 files changed, 4800 insertions, 4038 deletions
diff --git a/lib/compiler/src/Makefile b/lib/compiler/src/Makefile index 299b2892fc..f75beaba20 100644 --- a/lib/compiler/src/Makefile +++ b/lib/compiler/src/Makefile @@ -50,6 +50,7 @@ MODULES = \ beam_asm \ beam_block \ beam_bool \ + beam_bs \ beam_bsm \ beam_clean \ beam_dead \ @@ -62,6 +63,7 @@ MODULES = \ beam_opcodes \ beam_peep \ beam_receive \ + beam_reorder \ beam_split \ beam_trim \ beam_type \ diff --git a/lib/compiler/src/beam_asm.erl b/lib/compiler/src/beam_asm.erl index a3201b0f4a..95be471de3 100644 --- a/lib/compiler/src/beam_asm.erl +++ b/lib/compiler/src/beam_asm.erl @@ -30,11 +30,12 @@ module(Code, Abst, SourceFile, Opts) -> {ok,assemble(Code, Abst, SourceFile, Opts)}. -assemble({Mod,Exp,Attr0,Asm0,NumLabels}, Abst, SourceFile, Opts) -> +assemble({Mod,Exp0,Attr0,Asm0,NumLabels}, Abst, SourceFile, Opts) -> {1,Dict0} = beam_dict:atom(Mod, beam_dict:new()), {0,Dict1} = beam_dict:fname(atom_to_list(Mod) ++ ".erl", Dict0), NumFuncs = length(Asm0), {Asm,Attr} = on_load(Asm0, Attr0), + Exp = cerl_sets:from_list(Exp0), {Code,Dict2} = assemble_1(Asm, Exp, Dict1, []), build_file(Code, Attr, Dict2, NumLabels, NumFuncs, Abst, SourceFile, Opts). @@ -61,7 +62,7 @@ insert_on_load_instruction(Is0, Entry) -> Bef ++ [El,on_load|Is]. assemble_1([{function,Name,Arity,Entry,Asm}|T], Exp, Dict0, Acc) -> - Dict1 = case member({Name,Arity}, Exp) of + Dict1 = case cerl_sets:is_element({Name,Arity}, Exp) of true -> beam_dict:export(Name, Arity, Entry, Dict0); false -> diff --git a/lib/compiler/src/beam_block.erl b/lib/compiler/src/beam_block.erl index 0321b1c07b..10dbaf462c 100644 --- a/lib/compiler/src/beam_block.erl +++ b/lib/compiler/src/beam_block.erl @@ -23,14 +23,13 @@ -module(beam_block). -export([module/2]). --import(lists, [mapfoldl/3,reverse/1,reverse/2,foldl/3,member/2]). --define(MAXREG, 1024). +-import(lists, [reverse/1,reverse/2,foldl/3,member/2]). -module({Mod,Exp,Attr,Fs0,Lc0}, _Opt) -> - {Fs,Lc} = mapfoldl(fun function/2, Lc0, Fs0), +module({Mod,Exp,Attr,Fs0,Lc}, _Opt) -> + Fs = [function(F) || F <- Fs0], {ok,{Mod,Exp,Attr,Fs,Lc}}. -function({function,Name,Arity,CLabel,Is0}, Lc0) -> +function({function,Name,Arity,CLabel,Is0}) -> try %% Collect basic blocks and optimize them. Is1 = blockify(Is0), @@ -40,11 +39,8 @@ function({function,Name,Arity,CLabel,Is0}, Lc0) -> Is5 = opt_blocks(Is4), Is6 = beam_utils:delete_live_annos(Is5), - %% Optimize bit syntax. - {Is,Lc} = bsm_opt(Is6, Lc0), - %% Done. - {{function,Name,Arity,CLabel,Is},Lc} + {function,Name,Arity,CLabel,Is6} catch Class:Error -> Stack = erlang:get_stacktrace(), @@ -62,56 +58,15 @@ blockify(Is) -> blockify([{loop_rec,{f,Fail},{x,0}},{loop_rec_end,_Lbl},{label,Fail}|Is], Acc) -> %% Useless instruction sequence. blockify(Is, Acc); -blockify([{test,is_atom,{f,Fail},[Reg]}=I| - [{select,select_val,Reg,{f,Fail}, - [{atom,false},{f,_}=BrFalse, - {atom,true}=AtomTrue,{f,_}=BrTrue]}|Is]=Is0], - [{block,Bl}|_]=Acc) -> - case is_last_bool(Bl, Reg) of - false -> - blockify(Is0, [I|Acc]); - true -> - %% The last instruction is a boolean operator/guard BIF that can't fail. - %% We can convert the three-way branch to a two-way branch (eliminating - %% the reference to the failure label). - blockify(Is, [{jump,BrTrue}, - {test,is_eq_exact,BrFalse,[Reg,AtomTrue]}|Acc]) - end; -blockify([{test,is_atom,{f,Fail},[Reg]}=I| - [{select,select_val,Reg,{f,Fail}, - [{atom,true}=AtomTrue,{f,_}=BrTrue, - {atom,false},{f,_}=BrFalse]}|Is]=Is0], - [{block,Bl}|_]=Acc) -> - case is_last_bool(Bl, Reg) of - false -> - blockify(Is0, [I|Acc]); - true -> - blockify(Is, [{jump,BrTrue}, - {test,is_eq_exact,BrFalse,[Reg,AtomTrue]}|Acc]) - end; blockify([I|Is0]=IsAll, Acc) -> - case is_bs_put(I) of - true -> - {BsPuts0,Is} = collect_bs_puts(IsAll), - BsPuts = opt_bs_puts(BsPuts0), - blockify(Is, reverse(BsPuts, Acc)); - false -> - case collect(I) of - error -> blockify(Is0, [I|Acc]); - Instr when is_tuple(Instr) -> - {Block,Is} = collect_block(IsAll), - blockify(Is, [{block,Block}|Acc]) - end + case collect(I) of + error -> blockify(Is0, [I|Acc]); + Instr when is_tuple(Instr) -> + {Block,Is} = collect_block(IsAll), + blockify(Is, [{block,Block}|Acc]) end; blockify([], Acc) -> reverse(Acc). -is_last_bool([{set,[Reg],As,{bif,N,_}}], Reg) -> - Ar = length(As), - erl_internal:new_type_test(N, Ar) orelse erl_internal:comp_op(N, Ar) - orelse erl_internal:bool_op(N, Ar); -is_last_bool([_|Is], Reg) -> is_last_bool(Is, Reg); -is_last_bool([], _) -> false. - collect_block(Is) -> collect_block(Is, []). @@ -149,7 +104,10 @@ collect({put_map,F,Op,S,D,R,{list,Puts}}) -> collect({get_map_elements,F,S,{list,Gets}}) -> {Ss,Ds} = beam_utils:split_even(Gets), {set,Ds,[S|Ss],{get_map_elements,F}}; -collect({'catch',R,L}) -> {set,[R],[],{'catch',L}}; +collect({'catch'=Op,R,L}) -> + {set,[R],[],{try_catch,Op,L}}; +collect({'try'=Op,R,L}) -> + {set,[R],[],{try_catch,Op,L}}; collect(fclearerror) -> {set,[],[],fclearerror}; collect({fcheckerror,{f,0}}) -> {set,[],[],fcheckerror}; collect({fmove,S,D}) -> {set,[D],[S],fmove}; @@ -183,7 +141,9 @@ opt_blocks([I|Is]) -> opt_blocks([]) -> []. opt_block(Is0) -> - Is = find_fixpoint(fun opt/1, Is0), + Is = find_fixpoint(fun(Is) -> + opt_tuple_element(opt(Is)) + end, Is0), opt_alloc(Is). find_fixpoint(OptFun, Is0) -> @@ -279,76 +239,151 @@ opt_moves([X0,Y0], Is0) -> not_possible -> {[X,Y0],Is2}; {X,_} -> {[X,Y0],Is2}; {Y,Is} -> {[X,Y],Is} - end; -opt_moves(Ds, Is) -> - %% multiple destinations -> pass through - {Ds,Is}. - + end. %% opt_move(Dest, [Instruction]) -> {UpdatedDest,[Instruction]} | not_possible %% If there is a {move,Dest,FinalDest} instruction %% in the instruction stream, remove the move instruction %% and let FinalDest be the destination. -%% -%% For this optimization to be safe, we must be sure that -%% Dest will not be referenced in any other by other instructions -%% in the rest of the instruction stream. Not even the indirect -%% reference by an instruction that may allocate (such as -%% test_heap/2 or a GC Bif) is allowed. opt_move(Dest, Is) -> - opt_move_1(Dest, Is, ?MAXREG, []). - -opt_move_1(R, [{set,_,_,{alloc,Live,_}}|_]=Is, SafeRegs, Acc) when Live < SafeRegs -> - %% Downgrade number of safe regs and rescan the instruction, as it most probably - %% is a gc_bif instruction. - opt_move_1(R, Is, Live, Acc); -opt_move_1(R, [{set,[{x,X}=D],[R],move}|Is], SafeRegs, Acc) -> - case X < SafeRegs andalso beam_utils:is_killed_block(R, Is) of - true -> opt_move_2(D, Acc, Is); - false -> not_possible + opt_move_1(Dest, Is, []). + +opt_move_1(R, [{set,[D],[R],move}|Is0], Acc) -> + %% Provided that the source register is killed by instructions + %% that follow, the optimization is safe. + case eliminate_use_of_from_reg(Is0, R, D, []) of + {yes,Is} -> opt_move_rev(D, Acc, Is); + no -> not_possible end; -opt_move_1(R, [{set,[D],[R],move}|Is], _SafeRegs, Acc) -> - case beam_utils:is_killed_block(R, Is) of - true -> opt_move_2(D, Acc, Is); - false -> not_possible +opt_move_1({x,_}, [{set,_,_,{alloc,_,_}}|_], _) -> + %% The optimization is not possible. If the X register is not + %% killed by allocation, the optimization would not be safe. + %% If the X register is killed, it means that there cannot + %% follow a 'move' instruction with this X register as the + %% source. + not_possible; +opt_move_1(R, [{set,_,_,_}=I|Is], Acc) -> + %% If the source register is either killed or used by this + %% instruction, the optimimization is not possible. + case is_killed_or_used(R, I) of + true -> not_possible; + false -> opt_move_1(R, Is, [I|Acc]) end; -opt_move_1(R, [I|Is], SafeRegs, Acc) -> - case is_transparent(R, I) of - false -> not_possible; - true -> opt_move_1(R, Is, SafeRegs, [I|Acc]) - end. +opt_move_1(_, _, _) -> + not_possible. + +%% opt_tuple_element([Instruction]) -> [Instruction] +%% If possible, move get_tuple_element instructions forward +%% in the instruction stream to a move instruction, eliminating +%% the move instruction. Example: +%% +%% get_tuple_element Tuple Pos Dst1 +%% ... +%% move Dst1 Dst2 +%% +%% This code may be possible to rewrite to: +%% +%% %%(Moved get_tuple_element instruction) +%% ... +%% get_tuple_element Tuple Pos Dst2 +%% -%% Reverse the instructions, while checking that there are no instructions that -%% would interfere with using the new destination register chosen. +opt_tuple_element([{set,[D],[S],{get_tuple_element,_}}=I|Is0]) -> + case opt_tuple_element_1(Is0, I, {S,D}, []) of + no -> + [I|opt_tuple_element(Is0)]; + {yes,Is} -> + opt_tuple_element(Is) + end; +opt_tuple_element([I|Is]) -> + [I|opt_tuple_element(Is)]; +opt_tuple_element([]) -> []. + +opt_tuple_element_1([{set,_,_,{alloc,_,_}}|_], _, _, _) -> + no; +opt_tuple_element_1([{set,_,_,{try_catch,_,_}}|_], _, _, _) -> + no; +opt_tuple_element_1([{set,[D],[S],move}|Is0], I0, {_,S}, Acc) -> + case eliminate_use_of_from_reg(Is0, S, D, []) of + no -> + no; + {yes,Is} -> + {set,[S],Ss,Op} = I0, + I = {set,[D],Ss,Op}, + {yes,reverse(Acc, [I|Is])} + end; +opt_tuple_element_1([{set,Ds,Ss,_}=I|Is], MovedI, {S,D}=Regs, Acc) -> + case member(S, Ds) orelse member(D, Ss) of + true -> + no; + false -> + opt_tuple_element_1(Is, MovedI, Regs, [I|Acc]) + end; +opt_tuple_element_1(_, _, _, _) -> no. + +%% Reverse the instructions, while checking that there are no +%% instructions that would interfere with using the new destination +%% register (D). -opt_move_2(D, [I|Is], Acc) -> - case is_transparent(D, I) of - false -> not_possible; - true -> opt_move_2(D, Is, [I|Acc]) +opt_move_rev(D, [I|Is], Acc) -> + case is_killed_or_used(D, I) of + true -> not_possible; + false -> opt_move_rev(D, Is, [I|Acc]) + end; +opt_move_rev(D, [], Acc) -> {D,Acc}. + +%% is_killed_or_used(Register, {set,_,_,_}) -> bool() +%% Test whether the register is used by the instruction. + +is_killed_or_used(R, {set,Ss,Ds,_}) -> + member(R, Ds) orelse member(R, Ss). + +%% eliminate_use_of_from_reg([Instruction], FromRegister, ToRegister, Acc) -> +%% {yes,Is} | no +%% Eliminate any use of FromRegister in the instruction sequence +%% by replacing uses of FromRegister with ToRegister. If FromRegister +%% is referenced by an allocation instruction, return 'no' to indicate +%% that FromRegister is still used and that the optimization is not +%% possible. + +eliminate_use_of_from_reg([{set,_,_,{alloc,Live,_}}|_]=Is0, {x,X}, _, Acc) -> + if + X < Live -> + no; + true -> + {yes,reverse(Acc, Is0)} end; -opt_move_2(D, [], Acc) -> {D,Acc}. - -%% is_transparent(Register, Instruction) -> true | false -%% Returns true if Instruction does not in any way references Register -%% (even indirectly by an allocation instruction). -%% Returns false if Instruction does reference Register, or we are -%% not sure. - -is_transparent({x,X}, {set,_,_,{alloc,Live,_}}) when X < Live -> - false; -is_transparent(R, {set,Ds,Ss,_Op}) -> - case member(R, Ds) of - true -> false; - false -> not member(R, Ss) +eliminate_use_of_from_reg([{set,Ds,Ss0,Op}=I0|Is], From, To, Acc) -> + I = case member(From, Ss0) of + true -> + Ss = [case S of + From -> To; + _ -> S + end || S <- Ss0], + {set,Ds,Ss,Op}; + false -> + I0 + end, + case member(From, Ds) of + true -> + {yes,reverse(Acc, [I|Is])}; + false -> + eliminate_use_of_from_reg(Is, From, To, [I|Acc]) end; -is_transparent(_, _) -> false. +eliminate_use_of_from_reg([I]=Is, From, _To, Acc) -> + case beam_utils:is_killed_block(From, [I]) of + true -> + {yes,reverse(Acc, Is)}; + false -> + no + end. %% opt_alloc(Instructions) -> Instructions' %% Optimises all allocate instructions. opt_alloc([{set,[],[],{alloc,R,{_,Ns,Nh,[]}}}|Is]) -> - [{set,[],[],opt_alloc(Is, Ns, Nh, R)}|opt(Is)]; + [{set,[],[],opt_alloc(Is, Ns, Nh, R)}|Is]; opt_alloc([I|Is]) -> [I|opt_alloc(Is)]; opt_alloc([]) -> []. @@ -414,234 +449,3 @@ x_dead([], Regs) -> Regs. x_live([{x,N}|Rs], Regs) -> x_live(Rs, Regs bor (1 bsl N)); x_live([_|Rs], Regs) -> x_live(Rs, Regs); x_live([], Regs) -> Regs. - -%%% -%%% Evaluation of constant bit fields. -%%% - -is_bs_put({bs_put,_,{bs_put_integer,_,_},_}) -> true; -is_bs_put({bs_put,_,{bs_put_float,_,_},_}) -> true; -is_bs_put(_) -> false. - -collect_bs_puts(Is) -> - collect_bs_puts_1(Is, []). - -collect_bs_puts_1([I|Is]=Is0, Acc) -> - case is_bs_put(I) of - false -> {reverse(Acc),Is0}; - true -> collect_bs_puts_1(Is, [I|Acc]) - end. - -opt_bs_puts(Is) -> - opt_bs_1(Is, []). - -opt_bs_1([{bs_put,Fail, - {bs_put_float,1,Flags0},[{integer,Sz},Src]}=I0|Is], Acc) -> - try eval_put_float(Src, Sz, Flags0) of - <<Int:Sz>> -> - Flags = force_big(Flags0), - I = {bs_put,Fail,{bs_put_integer,1,Flags}, - [{integer,Sz},{integer,Int}]}, - opt_bs_1([I|Is], Acc) - catch - error:_ -> - opt_bs_1(Is, [I0|Acc]) - end; -opt_bs_1([{bs_put,_,{bs_put_integer,1,_},[{integer,8},{integer,_}]}|_]=IsAll, - Acc0) -> - {Is,Acc} = bs_collect_string(IsAll, Acc0), - opt_bs_1(Is, Acc); -opt_bs_1([{bs_put,Fail,{bs_put_integer,1,F},[{integer,Sz},{integer,N}]}=I|Is0], - Acc) when Sz > 8 -> - case field_endian(F) of - big -> - %% We can do this optimization for any field size without risk - %% for code explosion. - case bs_split_int(N, Sz, Fail, Is0) of - no_split -> opt_bs_1(Is0, [I|Acc]); - Is -> opt_bs_1(Is, Acc) - end; - little when Sz < 128 -> - %% We only try to optimize relatively small fields, to avoid - %% an explosion in code size. - <<Int:Sz>> = <<N:Sz/little>>, - Flags = force_big(F), - Is = [{bs_put,Fail,{bs_put_integer,1,Flags}, - [{integer,Sz},{integer,Int}]}|Is0], - opt_bs_1(Is, Acc); - _ -> %native or too wide little field - opt_bs_1(Is0, [I|Acc]) - end; -opt_bs_1([{bs_put,Fail,{Op,U,F},[{integer,Sz},Src]}|Is], Acc) when U > 1 -> - opt_bs_1([{bs_put,Fail,{Op,1,F},[{integer,U*Sz},Src]}|Is], Acc); -opt_bs_1([I|Is], Acc) -> - opt_bs_1(Is, [I|Acc]); -opt_bs_1([], Acc) -> reverse(Acc). - -eval_put_float(Src, Sz, Flags) when Sz =< 256 -> %Only evaluate if Sz is reasonable. - Val = value(Src), - case field_endian(Flags) of - little -> <<Val:Sz/little-float-unit:1>>; - big -> <<Val:Sz/big-float-unit:1>> - %% native intentionally not handled here - we can't optimize it. - end. - -value({integer,I}) -> I; -value({float,F}) -> F. - -bs_collect_string(Is, [{bs_put,_,{bs_put_string,Len,{string,Str}},[]}|Acc]) -> - bs_coll_str_1(Is, Len, reverse(Str), Acc); -bs_collect_string(Is, Acc) -> - bs_coll_str_1(Is, 0, [], Acc). - -bs_coll_str_1([{bs_put,_,{bs_put_integer,U,_},[{integer,Sz},{integer,V}]}|Is], - Len, StrAcc, IsAcc) when U*Sz =:= 8 -> - Byte = V band 16#FF, - bs_coll_str_1(Is, Len+1, [Byte|StrAcc], IsAcc); -bs_coll_str_1(Is, Len, StrAcc, IsAcc) -> - {Is,[{bs_put,{f,0},{bs_put_string,Len,{string,reverse(StrAcc)}},[]}|IsAcc]}. - -field_endian({field_flags,F}) -> field_endian_1(F). - -field_endian_1([big=E|_]) -> E; -field_endian_1([little=E|_]) -> E; -field_endian_1([native=E|_]) -> E; -field_endian_1([_|Fs]) -> field_endian_1(Fs). - -force_big({field_flags,F}) -> - {field_flags,force_big_1(F)}. - -force_big_1([big|_]=Fs) -> Fs; -force_big_1([little|Fs]) -> [big|Fs]; -force_big_1([F|Fs]) -> [F|force_big_1(Fs)]. - -bs_split_int(0, Sz, _, _) when Sz > 64 -> - %% We don't want to split in this case because the - %% string will consist of only zeroes. - no_split; -bs_split_int(-1, Sz, _, _) when Sz > 64 -> - %% We don't want to split in this case because the - %% string will consist of only 255 bytes. - no_split; -bs_split_int(N, Sz, Fail, Acc) -> - FirstByteSz = case Sz rem 8 of - 0 -> 8; - Rem -> Rem - end, - bs_split_int_1(N, FirstByteSz, Sz, Fail, Acc). - -bs_split_int_1(-1, _, Sz, Fail, Acc) when Sz > 64 -> - I = {bs_put,Fail,{bs_put_integer,1,{field_flags,[big]}}, - [{integer,Sz},{integer,-1}]}, - [I|Acc]; -bs_split_int_1(0, _, Sz, Fail, Acc) when Sz > 64 -> - I = {bs_put,Fail,{bs_put_integer,1,{field_flags,[big]}}, - [{integer,Sz},{integer,0}]}, - [I|Acc]; -bs_split_int_1(N, ByteSz, Sz, Fail, Acc) when Sz > 0 -> - Mask = (1 bsl ByteSz) - 1, - I = {bs_put,Fail,{bs_put_integer,1,{field_flags,[big]}}, - [{integer,ByteSz},{integer,N band Mask}]}, - bs_split_int_1(N bsr ByteSz, 8, Sz-ByteSz, Fail, [I|Acc]); -bs_split_int_1(_, _, _, _, Acc) -> Acc. - - -%%% -%%% Optimization of new bit syntax matching: get rid -%%% of redundant bs_restore2/2 instructions across select_val -%%% instructions, as well as a few other simple peep-hole optimizations. -%%% - -bsm_opt(Is0, Lc0) -> - {Is1,D0,Lc} = bsm_scan(Is0, [], Lc0, []), - Is2 = case D0 of - [] -> - Is1; - _ -> - D = gb_trees:from_orddict(orddict:from_list(D0)), - bsm_reroute(Is1, D, none, []) - end, - Is = beam_clean:bs_clean_saves(Is2), - {bsm_opt_2(Is, []),Lc}. - -bsm_scan([{label,L}=Lbl,{bs_restore2,_,Save}=R|Is], D0, Lc, Acc0) -> - D = [{{L,Save},Lc}|D0], - Acc = [{label,Lc},R,Lbl|Acc0], - bsm_scan(Is, D, Lc+1, Acc); -bsm_scan([I|Is], D, Lc, Acc) -> - bsm_scan(Is, D, Lc, [I|Acc]); -bsm_scan([], D, Lc, Acc) -> - {reverse(Acc),D,Lc}. - -bsm_reroute([{bs_save2,Reg,Save}=I|Is], D, _, Acc) -> - bsm_reroute(Is, D, {Reg,Save}, [I|Acc]); -bsm_reroute([{bs_restore2,Reg,Save}=I|Is], D, _, Acc) -> - bsm_reroute(Is, D, {Reg,Save}, [I|Acc]); -bsm_reroute([{label,_}=I|Is], D, S, Acc) -> - bsm_reroute(Is, D, S, [I|Acc]); -bsm_reroute([{select,select_val,Reg,F0,Lbls0}|Is], D, {_,Save}=S, Acc0) -> - [F|Lbls] = bsm_subst_labels([F0|Lbls0], Save, D), - Acc = [{select,select_val,Reg,F,Lbls}|Acc0], - bsm_reroute(Is, D, S, Acc); -bsm_reroute([{test,TestOp,F0,TestArgs}=I|Is], D, {_,Save}=S, Acc0) -> - F = bsm_subst_label(F0, Save, D), - Acc = [{test,TestOp,F,TestArgs}|Acc0], - case bsm_not_bs_test(I) of - true -> - %% The test instruction will not update the bit offset for the - %% binary being matched. Therefore the save position can be kept. - bsm_reroute(Is, D, S, Acc); - false -> - %% The test instruction might update the bit offset. Kill our - %% remembered Save position. - bsm_reroute(Is, D, none, Acc) - end; -bsm_reroute([{test,TestOp,F0,Live,TestArgs,Dst}|Is], D, {_,Save}, Acc0) -> - F = bsm_subst_label(F0, Save, D), - Acc = [{test,TestOp,F,Live,TestArgs,Dst}|Acc0], - %% The test instruction will update the bit offset. Kill our - %% remembered Save position. - bsm_reroute(Is, D, none, Acc); -bsm_reroute([{block,[{set,[],[],{alloc,_,_}}]}=Bl, - {bs_context_to_binary,_}=I|Is], D, S, Acc) -> - %% To help further bit syntax optimizations. - bsm_reroute([I,Bl|Is], D, S, Acc); -bsm_reroute([I|Is], D, _, Acc) -> - bsm_reroute(Is, D, none, [I|Acc]); -bsm_reroute([], _, _, Acc) -> reverse(Acc). - -bsm_opt_2([{test,bs_test_tail2,F,[Ctx,Bits]}|Is], - [{test,bs_skip_bits2,F,[Ctx,{integer,I},Unit,_Flags]}|Acc]) -> - bsm_opt_2(Is, [{test,bs_test_tail2,F,[Ctx,Bits+I*Unit]}|Acc]); -bsm_opt_2([{test,bs_skip_bits2,F,[Ctx,{integer,I1},Unit1,_]}|Is], - [{test,bs_skip_bits2,F,[Ctx,{integer,I2},Unit2,Flags]}|Acc]) -> - bsm_opt_2(Is, [{test,bs_skip_bits2,F, - [Ctx,{integer,I1*Unit1+I2*Unit2},1,Flags]}|Acc]); -bsm_opt_2([I|Is], Acc) -> - bsm_opt_2(Is, [I|Acc]); -bsm_opt_2([], Acc) -> reverse(Acc). - -%% bsm_not_bs_test({test,Name,_,Operands}) -> true|false. -%% Test whether is the test is a "safe", i.e. does not move the -%% bit offset for a binary. -%% -%% 'true' means that the test is safe, 'false' that we don't know or -%% that the test moves the offset (e.g. bs_get_integer2). - -bsm_not_bs_test({test,bs_test_tail2,_,[_,_]}) -> true; -bsm_not_bs_test(Test) -> beam_utils:is_pure_test(Test). - -bsm_subst_labels(Fs, Save, D) -> - bsm_subst_labels_1(Fs, Save, D, []). - -bsm_subst_labels_1([F|Fs], Save, D, Acc) -> - bsm_subst_labels_1(Fs, Save, D, [bsm_subst_label(F, Save, D)|Acc]); -bsm_subst_labels_1([], _, _, Acc) -> - reverse(Acc). - -bsm_subst_label({f,Lbl0}=F, Save, D) -> - case gb_trees:lookup({Lbl0,Save}, D) of - {value,Lbl} -> {f,Lbl}; - none -> F - end; -bsm_subst_label(Other, _, _) -> Other. diff --git a/lib/compiler/src/beam_bool.erl b/lib/compiler/src/beam_bool.erl index d14be83496..efd935f666 100644 --- a/lib/compiler/src/beam_bool.erl +++ b/lib/compiler/src/beam_bool.erl @@ -25,8 +25,6 @@ -import(lists, [reverse/1,reverse/2,foldl/3,mapfoldl/3,map/2]). --define(MAXREG, 1024). - -record(st, {next, %Next label number. ll %Live regs at labels. diff --git a/lib/compiler/src/beam_bs.erl b/lib/compiler/src/beam_bs.erl new file mode 100644 index 0000000000..55fa7ce10c --- /dev/null +++ b/lib/compiler/src/beam_bs.erl @@ -0,0 +1,278 @@ +%% +%% %CopyrightBegin% +%% +%% Copyright Ericsson AB 1999-2013. All Rights Reserved. +%% +%% Licensed under the Apache License, Version 2.0 (the "License"); +%% you may not use this file except in compliance with the License. +%% You may obtain a copy of the License at +%% +%% http://www.apache.org/licenses/LICENSE-2.0 +%% +%% Unless required by applicable law or agreed to in writing, software +%% distributed under the License is distributed on an "AS IS" BASIS, +%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied. +%% See the License for the specific language governing permissions and +%% limitations under the License. +%% +%% %CopyrightEnd% +%% +%% Purpose : Partitions assembly instructions into basic blocks and +%% optimizes them. + +-module(beam_bs). + +-export([module/2]). +-import(lists, [mapfoldl/3,reverse/1]). + +module({Mod,Exp,Attr,Fs0,Lc0}, _Opt) -> + {Fs,Lc} = mapfoldl(fun function/2, Lc0, Fs0), + {ok,{Mod,Exp,Attr,Fs,Lc}}. + +function({function,Name,Arity,CLabel,Is0}, Lc0) -> + try + Is1 = bs_put_opt(Is0), + {Is,Lc} = bsm_opt(Is1, Lc0), + {{function,Name,Arity,CLabel,Is},Lc} + catch + Class:Error -> + Stack = erlang:get_stacktrace(), + io:fwrite("Function: ~w/~w\n", [Name,Arity]), + erlang:raise(Class, Error, Stack) + end. + +%%% +%%% Evaluation of constant bit fields. +%%% + +bs_put_opt([{bs_put,_,_,_}=I|Is0]) -> + {BsPuts0,Is} = collect_bs_puts(Is0, [I]), + BsPuts = opt_bs_puts(BsPuts0), + BsPuts ++ bs_put_opt(Is); +bs_put_opt([I|Is]) -> + [I|bs_put_opt(Is)]; +bs_put_opt([]) -> []. + +collect_bs_puts([{bs_put,_,_,_}=I|Is], Acc) -> + collect_bs_puts(Is, [I|Acc]); +collect_bs_puts([_|_]=Is, Acc) -> + {reverse(Acc),Is}. + +opt_bs_puts(Is) -> + opt_bs_1(Is, []). + +opt_bs_1([{bs_put,Fail, + {bs_put_float,1,Flags0},[{integer,Sz},Src]}=I0|Is], Acc) -> + try eval_put_float(Src, Sz, Flags0) of + <<Int:Sz>> -> + Flags = force_big(Flags0), + I = {bs_put,Fail,{bs_put_integer,1,Flags}, + [{integer,Sz},{integer,Int}]}, + opt_bs_1([I|Is], Acc) + catch + error:_ -> + opt_bs_1(Is, [I0|Acc]) + end; +opt_bs_1([{bs_put,_,{bs_put_integer,1,_},[{integer,8},{integer,_}]}|_]=IsAll, + Acc0) -> + {Is,Acc} = bs_collect_string(IsAll, Acc0), + opt_bs_1(Is, Acc); +opt_bs_1([{bs_put,Fail,{bs_put_integer,1,F},[{integer,Sz},{integer,N}]}=I|Is0], + Acc) when Sz > 8 -> + case field_endian(F) of + big -> + %% We can do this optimization for any field size without + %% risk for code explosion. + case bs_split_int(N, Sz, Fail, Is0) of + no_split -> opt_bs_1(Is0, [I|Acc]); + Is -> opt_bs_1(Is, Acc) + end; + little when Sz < 128 -> + %% We only try to optimize relatively small fields, to + %% avoid an explosion in code size. + <<Int:Sz>> = <<N:Sz/little>>, + Flags = force_big(F), + Is = [{bs_put,Fail,{bs_put_integer,1,Flags}, + [{integer,Sz},{integer,Int}]}|Is0], + opt_bs_1(Is, Acc); + _ -> %native or too wide little field + opt_bs_1(Is0, [I|Acc]) + end; +opt_bs_1([{bs_put,Fail,{Op,U,F},[{integer,Sz},Src]}|Is], Acc) when U > 1 -> + opt_bs_1([{bs_put,Fail,{Op,1,F},[{integer,U*Sz},Src]}|Is], Acc); +opt_bs_1([I|Is], Acc) -> + opt_bs_1(Is, [I|Acc]); +opt_bs_1([], Acc) -> reverse(Acc). + +eval_put_float(Src, Sz, Flags) when Sz =< 256 -> + %%Only evaluate if Sz is reasonable. + Val = value(Src), + case field_endian(Flags) of + little -> <<Val:Sz/little-float-unit:1>>; + big -> <<Val:Sz/big-float-unit:1>> + %% native intentionally not handled here - we can't optimize + %% it. + end. + +value({integer,I}) -> I; +value({float,F}) -> F. + +bs_collect_string(Is, [{bs_put,_,{bs_put_string,Len,{string,Str}},[]}|Acc]) -> + bs_coll_str_1(Is, Len, reverse(Str), Acc); +bs_collect_string(Is, Acc) -> + bs_coll_str_1(Is, 0, [], Acc). + +bs_coll_str_1([{bs_put,_,{bs_put_integer,U,_},[{integer,Sz},{integer,V}]}|Is], + Len, StrAcc, IsAcc) when U*Sz =:= 8 -> + Byte = V band 16#FF, + bs_coll_str_1(Is, Len+1, [Byte|StrAcc], IsAcc); +bs_coll_str_1(Is, Len, StrAcc, IsAcc) -> + {Is,[{bs_put,{f,0},{bs_put_string,Len,{string,reverse(StrAcc)}},[]}|IsAcc]}. + +field_endian({field_flags,F}) -> field_endian_1(F). + +field_endian_1([big=E|_]) -> E; +field_endian_1([little=E|_]) -> E; +field_endian_1([native=E|_]) -> E; +field_endian_1([_|Fs]) -> field_endian_1(Fs). + +force_big({field_flags,F}) -> + {field_flags,force_big_1(F)}. + +force_big_1([big|_]=Fs) -> Fs; +force_big_1([little|Fs]) -> [big|Fs]; +force_big_1([F|Fs]) -> [F|force_big_1(Fs)]. + +bs_split_int(0, Sz, _, _) when Sz > 64 -> + %% We don't want to split in this case because the + %% string will consist of only zeroes. + no_split; +bs_split_int(-1, Sz, _, _) when Sz > 64 -> + %% We don't want to split in this case because the + %% string will consist of only 255 bytes. + no_split; +bs_split_int(N, Sz, Fail, Acc) -> + FirstByteSz = case Sz rem 8 of + 0 -> 8; + Rem -> Rem + end, + bs_split_int_1(N, FirstByteSz, Sz, Fail, Acc). + +bs_split_int_1(-1, _, Sz, Fail, Acc) when Sz > 64 -> + I = {bs_put,Fail,{bs_put_integer,1,{field_flags,[big]}}, + [{integer,Sz},{integer,-1}]}, + [I|Acc]; +bs_split_int_1(0, _, Sz, Fail, Acc) when Sz > 64 -> + I = {bs_put,Fail,{bs_put_integer,1,{field_flags,[big]}}, + [{integer,Sz},{integer,0}]}, + [I|Acc]; +bs_split_int_1(N, ByteSz, Sz, Fail, Acc) when Sz > 0 -> + Mask = (1 bsl ByteSz) - 1, + I = {bs_put,Fail,{bs_put_integer,1,{field_flags,[big]}}, + [{integer,ByteSz},{integer,N band Mask}]}, + bs_split_int_1(N bsr ByteSz, 8, Sz-ByteSz, Fail, [I|Acc]); +bs_split_int_1(_, _, _, _, Acc) -> Acc. + +%%% +%%% Optimization of bit syntax matching: get rid +%%% of redundant bs_restore2/2 instructions across select_val +%%% instructions, as well as a few other simple peep-hole +%%% optimizations. +%%% + +bsm_opt(Is0, Lc0) -> + {Is1,D0,Lc} = bsm_scan(Is0, [], Lc0, []), + Is2 = case D0 of + [] -> + %% No bit syntax matching in this function. + Is1; + [_|_] -> + %% Optimize the bit syntax matching. + D = gb_trees:from_orddict(orddict:from_list(D0)), + bsm_reroute(Is1, D, none, []) + end, + Is = beam_clean:bs_clean_saves(Is2), + {bsm_opt_2(Is, []),Lc}. + +bsm_scan([{label,L}=Lbl,{bs_restore2,_,Save}=R|Is], D0, Lc, Acc0) -> + D = [{{L,Save},Lc}|D0], + Acc = [{label,Lc},R,Lbl|Acc0], + bsm_scan(Is, D, Lc+1, Acc); +bsm_scan([I|Is], D, Lc, Acc) -> + bsm_scan(Is, D, Lc, [I|Acc]); +bsm_scan([], D, Lc, Acc) -> + {reverse(Acc),D,Lc}. + +bsm_reroute([{bs_save2,Reg,Save}=I|Is], D, _, Acc) -> + bsm_reroute(Is, D, {Reg,Save}, [I|Acc]); +bsm_reroute([{bs_restore2,Reg,Save}=I|Is], D, _, Acc) -> + bsm_reroute(Is, D, {Reg,Save}, [I|Acc]); +bsm_reroute([{label,_}=I|Is], D, S, Acc) -> + bsm_reroute(Is, D, S, [I|Acc]); +bsm_reroute([{select,select_val,Reg,F0,Lbls0}|Is], D, {_,Save}=S, Acc0) -> + [F|Lbls] = bsm_subst_labels([F0|Lbls0], Save, D), + Acc = [{select,select_val,Reg,F,Lbls}|Acc0], + bsm_reroute(Is, D, S, Acc); +bsm_reroute([{test,TestOp,F0,TestArgs}=I|Is], D, {_,Save}=S, Acc0) -> + F = bsm_subst_label(F0, Save, D), + Acc = [{test,TestOp,F,TestArgs}|Acc0], + case bsm_not_bs_test(I) of + true -> + %% The test instruction will not update the bit offset for + %% the binary being matched. Therefore the save position + %% can be kept. + bsm_reroute(Is, D, S, Acc); + false -> + %% The test instruction might update the bit offset. Kill + %% our remembered Save position. + bsm_reroute(Is, D, none, Acc) + end; +bsm_reroute([{test,TestOp,F0,Live,TestArgs,Dst}|Is], D, {_,Save}, Acc0) -> + F = bsm_subst_label(F0, Save, D), + Acc = [{test,TestOp,F,Live,TestArgs,Dst}|Acc0], + %% The test instruction will update the bit offset. Kill our + %% remembered Save position. + bsm_reroute(Is, D, none, Acc); +bsm_reroute([{block,[{set,[],[],{alloc,_,_}}]}=Bl, + {bs_context_to_binary,_}=I|Is], D, S, Acc) -> + %% To help further bit syntax optimizations. + bsm_reroute([I,Bl|Is], D, S, Acc); +bsm_reroute([I|Is], D, _, Acc) -> + bsm_reroute(Is, D, none, [I|Acc]); +bsm_reroute([], _, _, Acc) -> reverse(Acc). + +bsm_opt_2([{test,bs_test_tail2,F,[Ctx,Bits]}|Is], + [{test,bs_skip_bits2,F,[Ctx,{integer,I},Unit,_Flags]}|Acc]) -> + bsm_opt_2(Is, [{test,bs_test_tail2,F,[Ctx,Bits+I*Unit]}|Acc]); +bsm_opt_2([{test,bs_skip_bits2,F,[Ctx,{integer,I1},Unit1,_]}|Is], + [{test,bs_skip_bits2,F,[Ctx,{integer,I2},Unit2,Flags]}|Acc]) -> + bsm_opt_2(Is, [{test,bs_skip_bits2,F, + [Ctx,{integer,I1*Unit1+I2*Unit2},1,Flags]}|Acc]); +bsm_opt_2([I|Is], Acc) -> + bsm_opt_2(Is, [I|Acc]); +bsm_opt_2([], Acc) -> reverse(Acc). + +%% bsm_not_bs_test({test,Name,_,Operands}) -> true|false. +%% Test whether is the test is a "safe", i.e. does not move the +%% bit offset for a binary. +%% +%% 'true' means that the test is safe, 'false' that we don't know or +%% that the test moves the offset (e.g. bs_get_integer2). + +bsm_not_bs_test({test,bs_test_tail2,_,[_,_]}) -> true; +bsm_not_bs_test(Test) -> beam_utils:is_pure_test(Test). + +bsm_subst_labels(Fs, Save, D) -> + bsm_subst_labels_1(Fs, Save, D, []). + +bsm_subst_labels_1([F|Fs], Save, D, Acc) -> + bsm_subst_labels_1(Fs, Save, D, [bsm_subst_label(F, Save, D)|Acc]); +bsm_subst_labels_1([], _, _, Acc) -> + reverse(Acc). + +bsm_subst_label({f,Lbl0}=F, Save, D) -> + case gb_trees:lookup({Lbl0,Save}, D) of + {value,Lbl} -> {f,Lbl}; + none -> F + end; +bsm_subst_label(Other, _, _) -> Other. diff --git a/lib/compiler/src/beam_clean.erl b/lib/compiler/src/beam_clean.erl index 919ee3ee7d..d9108c383d 100644 --- a/lib/compiler/src/beam_clean.erl +++ b/lib/compiler/src/beam_clean.erl @@ -141,7 +141,7 @@ renumber_labels([{bif,is_record,{f,_}, renumber_labels(Is, Acc, St); renumber_labels([{test,is_record,{f,_}=Fail, [Term,{atom,Tag}=TagAtom,{integer,Arity}]}|Is0], Acc, St) -> - Tmp = {x,1023}, + Tmp = {x,1022}, Is = case is_record_tuple(Term, Tag, Arity) of yes -> Is0; @@ -190,17 +190,11 @@ replace([{test,Test,{f,Lbl},Ops}|Is], Acc, D) -> replace([{test,Test,{f,Lbl},Live,Ops,Dst}|Is], Acc, D) -> replace(Is, [{test,Test,{f,label(Lbl, D)},Live,Ops,Dst}|Acc], D); replace([{select,I,R,{f,Fail0},Vls0}|Is], Acc, D) -> - Vls1 = map(fun ({f,L}) -> {f,label(L, D)}; - (Other) -> Other end, Vls0), + Vls = map(fun ({f,L}) -> {f,label(L, D)}; + (Other) -> Other + end, Vls0), Fail = label(Fail0, D), - case redundant_values(Vls1, Fail, []) of - [] -> - %% Oops, no choices left. The loader will not accept that. - %% Convert to a plain jump. - replace(Is, [{jump,{f,Fail}}|Acc], D); - Vls -> - replace(Is, [{select,I,R,{f,Fail},Vls}|Acc], D) - end; + replace(Is, [{select,I,R,{f,Fail},Vls}|Acc], D); replace([{'try',R,{f,Lbl}}|Is], Acc, D) -> replace(Is, [{'try',R,{f,label(Lbl, D)}}|Acc], D); replace([{'catch',R,{f,Lbl}}|Is], Acc, D) -> @@ -241,12 +235,6 @@ label(Old, D) -> {value,Val} -> Val; none -> throw({error,{undefined_label,Old}}) end. - -redundant_values([_,{f,Fail}|Vls], Fail, Acc) -> - redundant_values(Vls, Fail, Acc); -redundant_values([Val,Lbl|Vls], Fail, Acc) -> - redundant_values(Vls, Fail, [Lbl,Val|Acc]); -redundant_values([], _, Acc) -> reverse(Acc). %%% %%% Final fixup of bs_start_match2/5,bs_save2/bs_restore2 instructions for diff --git a/lib/compiler/src/beam_dead.erl b/lib/compiler/src/beam_dead.erl index ead88b57e9..11129c39bc 100644 --- a/lib/compiler/src/beam_dead.erl +++ b/lib/compiler/src/beam_dead.erl @@ -239,11 +239,26 @@ backward([{test,is_eq_exact,Fail,[Dst,{integer,Arity}]}=I| backward([{label,Lbl}=L|Is], D, Acc) -> backward(Is, beam_utils:index_label(Lbl, Acc, D), [L|Acc]); backward([{select,select_val,Reg,{f,Fail0},List0}|Is], D, Acc) -> - List = shortcut_select_list(List0, Reg, D, []), + List1 = shortcut_select_list(List0, Reg, D, []), Fail1 = shortcut_label(Fail0, D), Fail = shortcut_bs_test(Fail1, Is, D), - Sel = {select,select_val,Reg,{f,Fail},List}, - backward(Is, D, [Sel|Acc]); + List = prune_redundant(List1, Fail), + case List of + [] -> + Jump = {jump,{f,Fail}}, + backward([Jump|Is], D, Acc); + [V,F] -> + Test = {test,is_eq_exact,{f,Fail},[Reg,V]}, + Jump = {jump,F}, + backward([Jump,Test|Is], D, Acc); + [{atom,B1},F,{atom,B2},F] when B1 =:= not B2 -> + Test = {test,is_boolean,{f,Fail},[Reg]}, + Jump = {jump,F}, + backward([Jump,Test|Is], D, Acc); + [_|_] -> + Sel = {select,select_val,Reg,{f,Fail},List}, + backward(Is, D, [Sel|Acc]) + end; backward([{jump,{f,To0}},{move,Src,Reg}=Move|Is], D, Acc) -> To = shortcut_select_label(To0, Reg, Src, D), Jump = {jump,{f,To}}, @@ -257,14 +272,17 @@ backward([{jump,{f,To}}=J|[{bif,Op,_,Ops,Reg}|Is]=Is0], D, Acc) -> catch throw:not_possible -> backward(Is0, D, [J|Acc]) end; -backward([{test,bs_start_match2,F,_,[R,_],Ctxt}=I|Is], D, +backward([{test,bs_start_match2,F,Live,[R,_]=Args,Ctxt}|Is], D, [{test,bs_match_string,F,[Ctxt,Bs]}, {test,bs_test_tail2,F,[Ctxt,0]}|Acc0]=Acc) -> + {f,To0} = F, + To = shortcut_bs_start_match(To0, R, D), case beam_utils:is_killed(Ctxt, Acc0, D) of true -> - Eq = {test,is_eq_exact,F,[R,{literal,Bs}]}, + Eq = {test,is_eq_exact,{f,To},[R,{literal,Bs}]}, backward(Is, D, [Eq|Acc0]); false -> + I = {test,bs_start_match2,{f,To},Live,Args,Ctxt}, backward(Is, D, [I|Acc]) end; backward([{test,bs_start_match2,{f,To0},Live,[Src|_]=Info,Dst}|Is], D, Acc) -> @@ -295,7 +313,28 @@ backward([{test,Op,{f,To0},Ops0}|Is], D, Acc) -> is_eq_exact -> combine_eqs(To, Ops0, D, Acc); _ -> {test,Op,{f,To},Ops0} end, - backward(Is, D, [I|Acc]); + case {I,Acc} of + {{test,is_atom,Fail,Ops0},[{test,is_boolean,Fail,Ops0}|_]} -> + %% An is_atom test before an is_boolean test (with the + %% same failure label) is redundant. + backward(Is, D, Acc); + {{test,is_atom,Fail,[R]}, + [{test,is_eq_exact,Fail,[R,{atom,_}]}|_]} -> + %% An is_atom test before a comparison with an atom (with + %% the same failure label) is redundant. + backward(Is, D, Acc); + {{test,is_integer,Fail,[R]}, + [{test,is_eq_exact,Fail,[R,{integer,_}]}|_]} -> + %% An is_integer test before a comparison with an integer + %% (with the same failure label) is redundant. + backward(Is, D, Acc); + {{test,_,_,_},_} -> + %% Still a test instruction. Done. + backward(Is, D, [I|Acc]); + {_,_} -> + %% Rewritten to a select_val. Rescan. + backward([I|Is], D, Acc) + end; backward([{test,Op,{f,To0},Live,Ops0,Dst}|Is], D, Acc) -> To1 = shortcut_bs_test(To0, Is, D), To2 = shortcut_label(To1, D), @@ -348,6 +387,12 @@ shortcut_label(To0, D) -> shortcut_select_label(To, Reg, Lit, D) -> shortcut_rel_op(To, is_ne_exact, [Reg,Lit], D). +prune_redundant([_,{f,Fail}|T], Fail) -> + prune_redundant(T, Fail); +prune_redundant([V,F|T], Fail) -> + [V,F|prune_redundant(T, Fail)]; +prune_redundant([], _) -> []. + %% Replace a comparison operator with a test instruction and a jump. %% For example, if we have this code: %% diff --git a/lib/compiler/src/beam_dict.erl b/lib/compiler/src/beam_dict.erl index 2b5f8c1b7f..654fb47dbd 100644 --- a/lib/compiler/src/beam_dict.erl +++ b/lib/compiler/src/beam_dict.erl @@ -44,7 +44,7 @@ locals = [] :: [{label(), arity(), label()}], imports = gb_trees:empty() :: import_tab(), strings = <<>> :: binary(), %String pool - lambdas = [], %[{...}] + lambdas = {0,[]}, %[{...}] literals = dict:new() :: literal_tab(), fnames = #{} :: fname_tab(), lines = #{} :: line_tab(), @@ -145,15 +145,14 @@ string(Str, Dict) when is_list(Str) -> -spec lambda(label(), non_neg_integer(), bdict()) -> {non_neg_integer(), bdict()}. -lambda(Lbl, NumFree, #asm{lambdas=Lambdas0}=Dict) -> - OldIndex = length(Lambdas0), +lambda(Lbl, NumFree, #asm{lambdas={OldIndex,Lambdas0}}=Dict) -> %% Set Index the same as OldIndex. Index = OldIndex, %% Initialize OldUniq to 0. It will be set to an unique value %% based on the MD5 checksum of the BEAM code for the module. OldUniq = 0, Lambdas = [{Lbl,{OldIndex,Lbl,Index,NumFree,OldUniq}}|Lambdas0], - {OldIndex,Dict#asm{lambdas=Lambdas}}. + {OldIndex,Dict#asm{lambdas={OldIndex+1,Lambdas}}}. %% Returns the index for a literal (adding it to the literal table if necessary). %% literal(Literal, Dict) -> {Index,Dict'} @@ -236,13 +235,13 @@ string_table(#asm{strings=Strings,string_offset=Size}) -> -spec lambda_table(bdict()) -> {non_neg_integer(), [<<_:192>>]}. -lambda_table(#asm{locals=Loc0,lambdas=Lambdas0}) -> +lambda_table(#asm{locals=Loc0,lambdas={NumLambdas,Lambdas0}}) -> Lambdas1 = sofs:relation(Lambdas0), Loc = sofs:relation([{Lbl,{F,A}} || {F,A,Lbl} <- Loc0]), Lambdas2 = sofs:relative_product1(Lambdas1, Loc), Lambdas = [<<F:32,A:32,Lbl:32,Index:32,NumFree:32,OldUniq:32>> || {{_,Lbl,Index,NumFree,OldUniq},{F,A}} <- sofs:to_external(Lambdas2)], - {length(Lambdas),Lambdas}. + {NumLambdas,Lambdas}. %% Returns the literal table. %% literal_table(Dict) -> {NumLiterals, [<<TermSize>>,TermInExternalFormat]} diff --git a/lib/compiler/src/beam_jump.erl b/lib/compiler/src/beam_jump.erl index 5e58e0f6ac..3b6eb19fe8 100644 --- a/lib/compiler/src/beam_jump.erl +++ b/lib/compiler/src/beam_jump.erl @@ -495,7 +495,7 @@ is_label_used_in_block({set,_,_,Info}, Lbl) -> {alloc,_,{gc_bif,_,{f,F}}} -> F =:= Lbl; {alloc,_,{put_map,_,{f,F}}} -> F =:= Lbl; {get_map_elements,{f,F}} -> F =:= Lbl; - {'catch',{f,F}} -> F =:= Lbl; + {try_catch,_,{f,F}} -> F =:= Lbl; {alloc,_,_} -> false; {put_tuple,_} -> false; {get_tuple_element,_} -> false; diff --git a/lib/compiler/src/beam_peep.erl b/lib/compiler/src/beam_peep.erl index 17fd2e502a..0c1abfe6a0 100644 --- a/lib/compiler/src/beam_peep.erl +++ b/lib/compiler/src/beam_peep.erl @@ -65,18 +65,6 @@ function({function,Name,Arity,CLabel,Is0}) -> %% InEncoding =:= latin1, OutEncoding =:= unicode; %% InEncoding =:= latin1, OutEncoding =:= utf8 -> %% -%% (2) A select_val/4 instruction that only verifies that -%% its argument is either 'true' or 'false' can be -%% be replaced with an is_boolean/2 instruction. That is: -%% -%% select_val Reg Fail [ true Next false Next ] -%% Next: ... -%% -%% can be rewritten to -%% -%% is_boolean Fail Reg -%% Next: ... -%% peep(Is) -> peep(Is, gb_sets:empty(), []). @@ -95,12 +83,16 @@ peep([{gc_bif,_,_,_,_,Dst}=I|Is], SeenTests0, Acc) -> %% Kill all remembered tests that depend on the destination register. SeenTests = kill_seen(Dst, SeenTests0), peep(Is, SeenTests, [I|Acc]); -peep([{test,is_boolean,{f,Fail},Ops}|_]=Is, SeenTests, - [{test,is_atom,{f,Fail},Ops}|Acc]) -> - %% The previous is_atom/2 test (with the same failure label) is redundant. - %% (If is_boolean(Src) is true, is_atom(Src) is also true, so it is - %% OK to still remember that we have seen is_atom/1.) - peep(Is, SeenTests, Acc); +peep([{select,Op,R,F,Vls0}|Is], _, Acc) -> + case prune_redundant_values(Vls0, F) of + [] -> + %% No values left. Must convert to plain jump. + I = {jump,F}, + peep(Is, gb_sets:empty(), [I|Acc]); + [_|_]=Vls -> + I = {select,Op,R,F,Vls}, + peep(Is, gb_sets:empty(), [I|Acc]) + end; peep([{test,Op,_,Ops}=I|Is], SeenTests0, Acc) -> case beam_utils:is_pure_test(I) of false -> @@ -121,16 +113,6 @@ peep([{test,Op,_,Ops}=I|Is], SeenTests0, Acc) -> peep(Is, SeenTests, [I|Acc]) end end; -peep([{select,select_val,Src,Fail, - [{atom,false},{f,L},{atom,true},{f,L}]}| - [{label,L}|_]=Is], SeenTests, Acc) -> - I = {test,is_boolean,Fail,[Src]}, - peep([I|Is], SeenTests, Acc); -peep([{select,select_val,Src,Fail, - [{atom,true},{f,L},{atom,false},{f,L}]}| - [{label,L}|_]=Is], SeenTests, Acc) -> - I = {test,is_boolean,Fail,[Src]}, - peep([I|Is], SeenTests, Acc); peep([I|Is], _, Acc) -> %% An unknown instruction. Throw away all information we %% have collected about test instructions. @@ -155,3 +137,9 @@ kill_seen_1([{_,Ops}=Test|T], Dst) -> false -> [Test|kill_seen_1(T, Dst)] end; kill_seen_1([], _) -> []. + +prune_redundant_values([_Val,F|Vls], F) -> + prune_redundant_values(Vls, F); +prune_redundant_values([Val,Lbl|Vls], F) -> + [Val,Lbl|prune_redundant_values(Vls, F)]; +prune_redundant_values([], _) -> []. diff --git a/lib/compiler/src/beam_reorder.erl b/lib/compiler/src/beam_reorder.erl new file mode 100644 index 0000000000..41586a7bf2 --- /dev/null +++ b/lib/compiler/src/beam_reorder.erl @@ -0,0 +1,139 @@ +%% +%% %CopyrightBegin% +%% +%% Copyright Ericsson AB 1999-2013. All Rights Reserved. +%% +%% Licensed under the Apache License, Version 2.0 (the "License"); +%% you may not use this file except in compliance with the License. +%% You may obtain a copy of the License at +%% +%% http://www.apache.org/licenses/LICENSE-2.0 +%% +%% Unless required by applicable law or agreed to in writing, software +%% distributed under the License is distributed on an "AS IS" BASIS, +%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied. +%% See the License for the specific language governing permissions and +%% limitations under the License. +%% +%% %CopyrightEnd% +%% + +-module(beam_reorder). + +-export([module/2]). +-import(lists, [member/2,reverse/1]). + +module({Mod,Exp,Attr,Fs0,Lc}, _Opt) -> + Fs = [function(F) || F <- Fs0], + {ok,{Mod,Exp,Attr,Fs,Lc}}. + +function({function,Name,Arity,CLabel,Is0}) -> + try + Is = reorder(Is0), + {function,Name,Arity,CLabel,Is} + catch + Class:Error -> + Stack = erlang:get_stacktrace(), + io:fwrite("Function: ~w/~w\n", [Name,Arity]), + erlang:raise(Class, Error, Stack) + end. + +%% reorder(Instructions0) -> Instructions +%% Reorder instructions before the beam_block pass, because reordering +%% will be more cumbersome when the blocks are in place. +%% +%% Execution of get_tuple_element instructions can be delayed until +%% they are actually needed. Consider the sequence: +%% +%% get_tuple_element Tuple Pos Dst +%% test Test Fail Operands +%% +%% If Dst is killed at label Fail (and not referenced in Operands), +%% we can can swap the instructions: +%% +%% test Test Fail Operands +%% get_tuple_element Tuple Pos Dst +%% +%% That can be beneficial in two ways: Firstly, if the branch is taken +%% we have avoided execution of the get_tuple_element instruction. +%% Secondly, even if the branch is not taken, subsequent optimization +%% (opt_blocks/1) may be able to change Dst to the final destination +%% register and eliminate a 'move' instruction. + +reorder(Is) -> + D = beam_utils:index_labels(Is), + reorder_1(Is, D, []). + +reorder_1([{Op,_,_}=TryCatch|[I|Is]=Is0], D, Acc) + when Op =:= 'catch'; Op =:= 'try' -> + %% Don't allow 'try' or 'catch' instructions to split blocks if + %% it can be avoided. + case is_safe(I) of + false -> + reorder_1(Is0, D, [TryCatch|Acc]); + true -> + reorder_1([TryCatch|Is], D, [I|Acc]) + end; +reorder_1([{label,L}=I|_], D, Acc) -> + Is = beam_utils:code_at(L, D), + reorder_1(Is, D, [I|Acc]); +reorder_1([{test,is_nonempty_list,_,_}=I|Is], D, Acc) -> + %% The run-time system may combine the is_nonempty_list test with + %% the following get_list instruction. + reorder_1(Is, D, [I|Acc]); +reorder_1([{test,_,_,_}=I, + {select,_,_,_,_}=S|Is], D, Acc) -> + %% There is nothing to gain by inserting a get_tuple_element + %% instruction between the test instruction and the select + %% instruction. + reorder_1(Is, D, [S,I|Acc]); +reorder_1([{test,_,{f,L},Ss}=I|Is0], D0, + [{get_tuple_element,_,_,El}=G|Acc0]=Acc) -> + case member(El, Ss) of + true -> + reorder_1(Is0, D0, [I|Acc]); + false -> + case beam_utils:is_killed_at(El, L, D0) of + true -> + Is = [I,G|Is0], + reorder_1(Is, D0, Acc0); + false -> + case beam_utils:is_killed(El, Is0, D0) of + true -> + Code0 = beam_utils:code_at(L, D0), + Code = [G|Code0], + D = beam_utils:index_label(L, Code, D0), + Is = [I|Is0], + reorder_1(Is, D, Acc0); + false -> + reorder_1(Is0, D0, [I|Acc]) + end + end + end; +reorder_1([{allocate_zero,N,Live}=I0|Is], D, + [{get_tuple_element,{x,Tup},_,{x,Dst}}=G|Acc]=Acc0) -> + case Tup < Dst andalso Dst+1 =:= Live of + true -> + %% Move allocation instruction upwards past + %% get_tuple_element instructions to create more + %% opportunities for moving get_tuple_element + %% instructions. + I = {allocate_zero,N,Dst}, + reorder_1([I,G|Is], D, Acc); + false -> + reorder_1(Is, D, [I0|Acc0]) + end; +reorder_1([I|Is], D, Acc) -> + reorder_1(Is, D, [I|Acc]); +reorder_1([], _, Acc) -> reverse(Acc). + +%% is_safe(Instruction) -> true|false +%% Test whether an instruction is safe (cannot cause an exception). + +is_safe({kill,_}) -> true; +is_safe({move,_,_}) -> true; +is_safe({put,_}) -> true; +is_safe({put_list,_,_,_}) -> true; +is_safe({put_tuple,_,_}) -> true; +is_safe({test_heap,_,_}) -> true; +is_safe(_) -> false. diff --git a/lib/compiler/src/beam_split.erl b/lib/compiler/src/beam_split.erl index 3be9311080..bb1c0e23a9 100644 --- a/lib/compiler/src/beam_split.erl +++ b/lib/compiler/src/beam_split.erl @@ -57,8 +57,8 @@ split_block([{set,[D],[S|Puts],{alloc,R,{put_map,Op,{f,Lbl}=Fail}}}|Is], split_block([{set,Ds,[S|Ss],{get_map_elements,Fail}}|Is], Bl, Acc) -> Gets = beam_utils:join_even(Ss,Ds), split_block(Is, [], [{get_map_elements,Fail,S,{list,Gets}}|make_block(Bl, Acc)]); -split_block([{set,[R],[],{'catch',L}}|Is], Bl, Acc) -> - split_block(Is, [], [{'catch',R,L}|make_block(Bl, Acc)]); +split_block([{set,[R],[],{try_catch,Op,L}}|Is], Bl, Acc) -> + split_block(Is, [], [{Op,R,L}|make_block(Bl, Acc)]); split_block([{set,[],[],{line,_}=Line}|Is], Bl, Acc) -> split_block(Is, [], [Line|make_block(Bl, Acc)]); split_block([I|Is], Bl, Acc) -> diff --git a/lib/compiler/src/beam_type.erl b/lib/compiler/src/beam_type.erl index 5298589f83..4b45c28623 100644 --- a/lib/compiler/src/beam_type.erl +++ b/lib/compiler/src/beam_type.erl @@ -23,7 +23,8 @@ -export([module/2]). --import(lists, [foldl/3,reverse/1,filter/2]). +-import(lists, [filter/2,foldl/3,keyfind/3,member/2, + reverse/1,reverse/2,sort/1]). module({Mod,Exp,Attr,Fs0,Lc}, _Opts) -> Fs = [function(F) || F <- Fs0], @@ -92,8 +93,19 @@ simplify_basic_1([{set,[D],[TupleReg],{get_tuple_element,0}}=I|Is0], Ts0, Acc) - Ts = update(I, Ts0), simplify_basic_1(Is0, Ts, [I|Acc]) end; -simplify_basic_1([{set,_,_,{'catch',_}}=I|Is], _Ts, Acc) -> +simplify_basic_1([{set,_,_,{try_catch,_,_}}=I|Is], _Ts, Acc) -> simplify_basic_1(Is, tdb_new(), [I|Acc]); +simplify_basic_1([{test,is_atom,_,[R]}=I|Is], Ts, Acc) -> + case tdb_find(R, Ts) of + boolean -> simplify_basic_1(Is, Ts, Acc); + _ -> simplify_basic_1(Is, Ts, [I|Acc]) + end; +simplify_basic_1([{test,is_integer,_,[R]}=I|Is], Ts, Acc) -> + case tdb_find(R, Ts) of + integer -> simplify_basic_1(Is, Ts, Acc); + {integer,_} -> simplify_basic_1(Is, Ts, Acc); + _ -> simplify_basic_1(Is, Ts, [I|Acc]) + end; simplify_basic_1([{test,is_tuple,_,[R]}=I|Is], Ts, Acc) -> case tdb_find(R, Ts) of {tuple,_,_} -> simplify_basic_1(Is, Ts, Acc); @@ -137,6 +149,16 @@ simplify_basic_1([{test,is_record,_,[R,{atom,_}=Tag,{integer,Arity}]}=I|Is], Ts0 Ts = update(I, Ts0), simplify_basic_1(Is, Ts, [I|Acc]) end; +simplify_basic_1([{select,select_val,Reg,_,_}=I0|Is], Ts, Acc) -> + I = case tdb_find(Reg, Ts) of + {integer,Range} -> + simplify_select_val_int(I0, Range); + boolean -> + simplify_select_val_bool(I0); + _ -> + I0 + end, + simplify_basic_1(Is, tdb_new(), [I|Acc]); simplify_basic_1([I|Is], Ts0, Acc) -> Ts = update(I, Ts0), simplify_basic_1(Is, Ts, [I|Acc]); @@ -144,6 +166,32 @@ simplify_basic_1([], Ts, Acc) -> Is = reverse(Acc), {Is,Ts}. +simplify_select_val_int({select,select_val,R,_,L0}=I, {Min,Max}) -> + Vs = sort([V || {integer,V} <- L0]), + case eq_ranges(Vs, Min, Max) of + false -> I; + true -> simplify_select_val_1(L0, {integer,Max}, R, []) + end. + +simplify_select_val_bool({select,select_val,R,_,L}=I) -> + Vs = sort([V || {atom,V} <- L]), + case Vs of + [false,true] -> + simplify_select_val_1(L, {atom,false}, R, []); + _ -> + I + end. + +simplify_select_val_1([Val,F|T], Val, R, Acc) -> + L = reverse(Acc, T), + {select,select_val,R,F,L}; +simplify_select_val_1([V,F|T], Val, R, Acc) -> + simplify_select_val_1(T, Val, R, [F,V|Acc]). + +eq_ranges([H], H, H) -> true; +eq_ranges([H|T], H, Max) -> eq_ranges(T, H+1, Max); +eq_ranges(_, _, _) -> false. + %% simplify_float([Instruction], TypeDatabase) -> %% {[Instruction],TypeDatabase'} | not_possible %% Simplify floating point operations in blocks. @@ -199,7 +247,7 @@ simplify_float_1([{set,[D0],[A0,B0],{alloc,_,{gc_bif,Op0,{f,0}}}}=I|Is]=Is0, Ts = tdb_update([{D0,float}], Ts0), simplify_float_1(Is, Ts, Rs, Acc) end; -simplify_float_1([{set,_,_,{'catch',_}}=I|Is]=Is0, _Ts, Rs0, Acc0) -> +simplify_float_1([{set,_,_,{try_catch,_,_}}=I|Is]=Is0, _Ts, Rs0, Acc0) -> Acc = flush_all(Rs0, Is0, Acc0), simplify_float_1(Is, tdb_new(), Rs0, [I|Acc]); simplify_float_1([{set,_,_,{line,_}}=I|Is], Ts, Rs, Acc) -> @@ -311,7 +359,7 @@ flt_need_heap_2({set,_,_,{get_tuple_element,_}}, H, Fl) -> {[],H,Fl}; flt_need_heap_2({set,_,_,get_list}, H, Fl) -> {[],H,Fl}; -flt_need_heap_2({set,_,_,{'catch',_}}, H, Fl) -> +flt_need_heap_2({set,_,_,{try_catch,_,_}}, H, Fl) -> {[],H,Fl}; %% All other instructions should cause the insertion of an allocation %% instruction if needed. @@ -382,6 +430,17 @@ update({set,[D],[{integer,I},Reg],{bif,element,_}}, Ts0) -> tdb_update([{Reg,{tuple,I,[]}},{D,kill}], Ts0); update({set,[D],[_Index,Reg],{bif,element,_}}, Ts0) -> tdb_update([{Reg,{tuple,0,[]}},{D,kill}], Ts0); +update({set,[D],Args,{bif,N,_}}, Ts0) -> + Ar = length(Args), + BoolOp = erl_internal:new_type_test(N, Ar) orelse + erl_internal:comp_op(N, Ar) orelse + erl_internal:bool_op(N, Ar), + case BoolOp of + true -> + tdb_update([{D,boolean}], Ts0); + false -> + tdb_update([{D,kill}], Ts0) + end; update({set,[D],[S],{get_tuple_element,0}}, Ts) -> tdb_update([{D,{tuple_element,S,0}}], Ts); update({set,[D],[S],{alloc,_,{gc_bif,float,{f,0}}}}, Ts0) -> @@ -390,6 +449,13 @@ update({set,[D],[S],{alloc,_,{gc_bif,float,{f,0}}}}, Ts0) -> true -> tdb_update([{D,float}], Ts0); false -> Ts0 end; +update({set,[D],[S1,S2],{alloc,_,{gc_bif,'band',{f,0}}}}, Ts) -> + case keyfind(integer, 1, [S1,S2]) of + {integer,N} -> + update_band(N, D, Ts); + false -> + tdb_update([{D,integer}], Ts) + end; update({set,[D],[S1,S2],{alloc,_,{gc_bif,'/',{f,0}}}}, Ts0) -> %% Make sure we reject non-numeric literals. case possibly_numeric(S1) andalso possibly_numeric(S2) of @@ -397,15 +463,17 @@ update({set,[D],[S1,S2],{alloc,_,{gc_bif,'/',{f,0}}}}, Ts0) -> false -> Ts0 end; update({set,[D],[S1,S2],{alloc,_,{gc_bif,Op,{f,0}}}}, Ts0) -> - case arith_op(Op) of - no -> - tdb_update([{D,kill}], Ts0); - {yes,_} -> + case op_type(Op) of + integer -> + tdb_update([{D,integer}], Ts0); + {float,_} -> case {tdb_find(S1, Ts0),tdb_find(S2, Ts0)} of {float,_} -> tdb_update([{D,float}], Ts0); {_,float} -> tdb_update([{D,float}], Ts0); {_,_} -> tdb_update([{D,kill}], Ts0) - end + end; + unknown -> + tdb_update([{D,kill}], Ts0) end; update({set,[],_Src,_Op}, Ts0) -> Ts0; update({set,[D],_Src,_Op}, Ts0) -> @@ -437,6 +505,8 @@ update({test,is_record,_Fail,[Src,Tag,{integer,Arity}]}, Ts) -> tdb_update([{Src,{tuple,Arity,[Tag]}}], Ts); update({test,_Test,_Fail,_Other}, Ts) -> Ts; +update({test,bs_get_integer2,_,_,Args,Dst}, Ts) -> + tdb_update([{Dst,get_bs_integer_type(Args)}], Ts); update({call_ext,Ar,{extfunc,math,Math,Ar}}, Ts) -> case is_math_bif(Math, Ar) of true -> tdb_update([{{x,0},float}], Ts); @@ -453,10 +523,43 @@ update({call,_Arity,_Func}, Ts) -> tdb_kill_xregs(Ts); update({call_ext,_Arity,_Func}, Ts) -> tdb_kill_xregs(Ts); update({make_fun2,_,_,_,_}, Ts) -> tdb_kill_xregs(Ts); update({line,_}, Ts) -> Ts; +update({bs_save2,_,_}, Ts) -> Ts; +update({bs_restore2,_,_}, Ts) -> Ts; %% The instruction is unknown. Kill all information. update(_I, _Ts) -> tdb_new(). +update_band(N, Reg, Ts) -> + Type = update_band_1(N, 0), + tdb_update([{Reg,Type}], Ts). + +update_band_1(N, Bits) when Bits < 64 -> + case 1 bsl Bits of + P when P =:= N + 1 -> + {integer,{0,N}}; + P when P > N + 1 -> + integer; + _ -> + update_band_1(N, Bits+1) + end; +update_band_1(_, _) -> + %% Negative or large positive number. Give up. + integer. + +get_bs_integer_type([_,{integer,N},U,{field_flags,Fl}]) + when N*U < 64 -> + NumBits = N*U, + case member(unsigned, Fl) of + true -> + {integer,{0,(1 bsl NumBits)-1}}; + false -> + %% Signed integer. Don't bother. + integer + end; +get_bs_integer_type(_) -> + %% Avoid creating ranges with a huge upper limit. + integer. + is_math_bif(cos, 1) -> true; is_math_bif(cosh, 1) -> true; is_math_bif(sin, 1) -> true; @@ -545,11 +648,22 @@ load_reg(V, Ts, Rs0, Is0) -> {Rs,Is} end. -arith_op('+') -> {yes,fadd}; -arith_op('-') -> {yes,fsub}; -arith_op('*') -> {yes,fmul}; -arith_op('/') -> {yes,fdiv}; -arith_op(_) -> no. +arith_op(Op) -> + case op_type(Op) of + {float,Instr} -> {yes,Instr}; + _ -> no + end. + +op_type('+') -> {float,fadd}; +op_type('-') -> {float,fsub}; +op_type('*') -> {float,fmul}; +%% '/' and 'band' are specially handled. +op_type('bor') -> integer; +op_type('bxor') -> integer; +op_type('bsl') -> integer; +op_type('bsr') -> integer; +op_type('div') -> integer; +op_type(_) -> unknown. flush(Rs, [{set,[_],[],{put_tuple,_}}|_]=Is0, Acc0) -> Acc = flush_all(Rs, Is0, Acc0), @@ -618,7 +732,6 @@ checkerror(Is) -> checkerror_1(Is, Is). checkerror_1([{set,[],[],fcheckerror}|_], OrigIs) -> OrigIs; -checkerror_1([{set,[],[],fclearerror}|_], OrigIs) -> OrigIs; checkerror_1([{set,_,_,{bif,fadd,_}}|_], OrigIs) -> checkerror_2(OrigIs); checkerror_1([{set,_,_,{bif,fsub,_}}|_], OrigIs) -> checkerror_2(OrigIs); checkerror_1([{set,_,_,{bif,fmul,_}}|_], OrigIs) -> checkerror_2(OrigIs); @@ -640,6 +753,9 @@ checkerror_2(OrigIs) -> [{set,[],[],fcheckerror}|OrigIs]. %%% of the first element). %%% %%% 'float' means that the register contains a float. +%%% +%%% 'integer' or {integer,{Min,Max}} that the register contains an +%%% integer. %% tdb_new() -> EmptyDataBase %% Creates a new, empty type database. @@ -729,10 +845,20 @@ merge_type_info({tuple,Sz1,[]}, {tuple,_Sz2,First}=Tuple2) -> merge_type_info({tuple,Sz1,First}, Tuple2); merge_type_info({tuple,_Sz1,First}=Tuple1, {tuple,Sz2,_}) -> merge_type_info(Tuple1, {tuple,Sz2,First}); +merge_type_info(integer, {integer,_}=Int) -> + Int; +merge_type_info({integer,_}=Int, integer) -> + Int; +merge_type_info({integer,{Min1,Max1}}, {integer,{Min2,Max2}}) -> + {integer,{max(Min1, Min2),min(Max1, Max2)}}; merge_type_info(NewType, _) -> verify_type(NewType), NewType. +verify_type(boolean) -> ok; +verify_type(integer) -> ok; +verify_type({integer,{Min,Max}}) + when is_integer(Min), is_integer(Max) -> ok; verify_type(map) -> ok; verify_type(nonempty_list) -> ok; verify_type({tuple,Sz,[]}) when is_integer(Sz) -> ok; diff --git a/lib/compiler/src/beam_utils.erl b/lib/compiler/src/beam_utils.erl index fbcd5de1bb..68d6105cfa 100644 --- a/lib/compiler/src/beam_utils.erl +++ b/lib/compiler/src/beam_utils.erl @@ -484,6 +484,15 @@ check_liveness(R, [{get_map_elements,{f,Fail},S,{list,L}}|Is], St0) -> Other end end; +check_liveness(R, [{test_heap,N,Live}|Is], St) -> + I = {block,[{set,[],[],{alloc,Live,{nozero,nostack,N,[]}}}]}, + check_liveness(R, [I|Is], St); +check_liveness(R, [{allocate_zero,N,Live}|Is], St) -> + I = {block,[{set,[],[],{alloc,Live,{zero,N,0,[]}}}]}, + check_liveness(R, [I|Is], St); +check_liveness(R, [{get_list,S,D1,D2}|Is], St) -> + I = {block,[{set,[D1,D2],[S],get_list}]}, + check_liveness(R, [I|Is], St); check_liveness(_R, Is, St) when is_list(Is) -> %% case Is of %% [I|_] -> diff --git a/lib/compiler/src/beam_validator.erl b/lib/compiler/src/beam_validator.erl index 6004f1974e..fd38fc0095 100644 --- a/lib/compiler/src/beam_validator.erl +++ b/lib/compiler/src/beam_validator.erl @@ -31,15 +31,6 @@ -import(lists, [reverse/1,foldl/3,foreach/2,dropwhile/2]). --define(MAXREG, 1024). - -%%-define(DEBUG, 1). --ifdef(DEBUG). --define(DBG_FORMAT(F, D), (io:format((F), (D)))). --else. --define(DBG_FORMAT(F, D), ok). --endif. - %% To be called by the compiler. module({Mod,Exp,Attr,Fs,Lc}=Code, _Opts) when is_atom(Mod), is_list(Exp), is_list(Attr), is_integer(Lc) -> @@ -170,29 +161,18 @@ validate_0(Module, [{function,Name,Ar,Entry,Code}|Fs], Ft) -> % in the module (those that start with bs_start_match2). }). --ifdef(DEBUG). -print_st(#st{x=Xs,y=Ys,numy=NumY,h=H,ct=Ct}) -> - io:format(" #st{x=~p~n" - " y=~p~n" - " numy=~p,h=~p,ct=~w~n", - [gb_trees:to_list(Xs),gb_trees:to_list(Ys),NumY,H,Ct]). --endif. - validate_1(Is, Name, Arity, Entry, Ft) -> validate_2(labels(Is), Name, Arity, Entry, Ft). validate_2({Ls1,[{func_info,{atom,Mod},{atom,Name},Arity}=_F|Is]}, Name, Arity, Entry, Ft) -> - lists:foreach(fun (_L) -> ?DBG_FORMAT(" ~p.~n", [{label,_L}]) end, Ls1), - ?DBG_FORMAT(" ~p.~n", [_F]), validate_3(labels(Is), Name, Arity, Entry, Mod, Ls1, Ft); validate_2({Ls1,Is}, Name, Arity, _Entry, _Ft) -> error({{'_',Name,Arity},{first(Is),length(Ls1),illegal_instruction}}). validate_3({Ls2,Is}, Name, Arity, Entry, Mod, Ls1, Ft) -> - lists:foreach(fun (_L) -> ?DBG_FORMAT(" ~p.~n", [{label,_L}]) end, Ls2), Offset = 1 + length(Ls1) + 1 + length(Ls2), - EntryOK = (Entry =:= undefined) orelse lists:member(Entry, Ls2), + EntryOK = lists:member(Entry, Ls2), if EntryOK -> St = init_state(Arity), @@ -260,7 +240,6 @@ valfun([], MFA, _Offset, #vst{branched=Targets0,labels=Labels0}=Vst) -> error({MFA,Error}) end; valfun([I|Is], MFA, Offset, Vst0) -> - ?DBG_FORMAT(" ~p.\n", [I]), valfun(Is, MFA, Offset+1, try Vst = val_dsetel(I, Vst0), @@ -278,7 +257,6 @@ valfun_1({label,Lbl}, #vst{current=St0,branched=B,labels=Lbls}=Vst) -> valfun_1(_I, #vst{current=none}=Vst) -> %% Ignore instructions after erlang:error/1,2, which %% the original R10B compiler thought would return. - ?DBG_FORMAT("Ignoring ~p\n", [_I]), Vst; valfun_1({badmatch,Src}, Vst) -> assert_term(Src, Vst), @@ -980,9 +958,9 @@ get_fls(#vst{current=#st{fls=Fls}}) when is_atom(Fls) -> Fls. init_fregs() -> 0. -set_freg({fr,Fr}, #vst{current=#st{f=Fregs0}=St}=Vst) +set_freg({fr,Fr}=Freg, #vst{current=#st{f=Fregs0}=St}=Vst) when is_integer(Fr), 0 =< Fr -> - limit_check(Fr), + check_limit(Freg), Bit = 1 bsl Fr, if Fregs0 band Bit =:= 0 -> @@ -995,9 +973,10 @@ set_freg(Fr, _) -> error({bad_target,Fr}). assert_freg_set({fr,Fr}=Freg, #vst{current=#st{f=Fregs}}) when is_integer(Fr), 0 =< Fr -> if - Fregs band (1 bsl Fr) =/= 0 -> - limit_check(Fr); - true -> error({uninitialized_reg,Freg}) + (Fregs bsr Fr) band 1 =:= 0 -> + error({uninitialized_reg,Freg}); + true -> + ok end; assert_freg_set(Fr, _) -> error({bad_source,Fr}). @@ -1076,16 +1055,16 @@ set_type(Type, {x,_}=Reg, Vst) -> set_type_reg(Type, Reg, Vst); set_type(Type, {y,_}=Reg, Vst) -> set_type_y(Type, Reg, Vst); set_type(_, _, #vst{}=Vst) -> Vst. -set_type_reg(Type, {x,X}, #vst{current=#st{x=Xs}=St}=Vst) +set_type_reg(Type, {x,X}=Reg, #vst{current=#st{x=Xs}=St}=Vst) when is_integer(X), 0 =< X -> - limit_check(X), + check_limit(Reg), Vst#vst{current=St#st{x=gb_trees:enter(X, Type, Xs)}}; set_type_reg(Type, Reg, Vst) -> set_type_y(Type, Reg, Vst). set_type_y(Type, {y,Y}=Reg, #vst{current=#st{y=Ys0}=St}=Vst) when is_integer(Y), 0 =< Y -> - limit_check(Y), + check_limit(Reg), Ys = case gb_trees:lookup(Y, Ys0) of none -> error({invalid_store,Reg,Type}); @@ -1612,17 +1591,19 @@ return_type_math(pow, 2) -> {float,[]}; return_type_math(pi, 0) -> {float,[]}; return_type_math(F, A) when is_atom(F), is_integer(A), A >= 0 -> term. -limit_check(Num) when is_integer(Num), Num >= ?MAXREG -> - error(limit); -limit_check(_) -> ok. +check_limit({x,X}) when is_integer(X), X < 1023 -> + %% Note: x(1023) is reserved for use by the BEAM loader. + ok; +check_limit({y,Y}) when is_integer(Y), Y < 1024 -> + ok; +check_limit({fr,Fr}) when is_integer(Fr), Fr < 1024 -> + ok; +check_limit(_) -> + error(limit). min(A, B) when is_integer(A), is_integer(B), A < B -> A; min(A, B) when is_integer(A), is_integer(B) -> B. gb_trees_from_list(L) -> gb_trees:from_orddict(lists:sort(L)). --ifdef(DEBUG). -error(Error) -> exit(Error). --else. error(Error) -> throw(Error). --endif. diff --git a/lib/compiler/src/cerl_trees.erl b/lib/compiler/src/cerl_trees.erl index 58bb18e34a..b86be95cab 100644 --- a/lib/compiler/src/cerl_trees.erl +++ b/lib/compiler/src/cerl_trees.erl @@ -27,7 +27,7 @@ -module(cerl_trees). -export([depth/1, fold/3, free_variables/1, get_label/1, label/1, label/2, - map/2, mapfold/3, size/1, variables/1]). + map/2, mapfold/3, mapfold/4, size/1, variables/1]). -import(cerl, [alias_pat/1, alias_var/1, ann_c_alias/3, ann_c_apply/3, ann_c_binary/2, ann_c_bitstr/6, ann_c_call/4, @@ -340,136 +340,162 @@ fold_pairs(_, S, []) -> %% starting with the given value <code>Initial</code>, while doing a %% post-order traversal of the tree, much like <code>fold/3</code>. %% +%% This is the same as mapfold/4, with an identity function as the +%% pre-operation. +%% %% @see map/2 %% @see fold/3 +%% @see mapfold/4 -spec mapfold(fun((cerl:cerl(), term()) -> {cerl:cerl(), term()}), term(), cerl:cerl()) -> {cerl:cerl(), term()}. mapfold(F, S0, T) -> + mapfold(fun(T0, A) -> {T0, A} end, F, S0, T). + + +%% @spec mapfold(Pre, Post, Initial::term(), Tree::cerl()) -> +%% {cerl(), term()} +%% +%% Pre = Post = (cerl(), term()) -> {cerl(), term()} +%% +%% @doc Does a combined map/fold operation on the nodes of the +%% tree. It begins by calling <code>Pre</code> on the tree, using the +%% <code>Initial</code> value. It then deconstructs the top node of +%% the returned tree and recurses on the children, using the returned +%% value as the new initial and carrying the returned values from one +%% call to the next. Finally it reassembles the top node from the +%% children, calls <code>Post</code> on it and returns the result. + +-spec mapfold(fun((cerl:cerl(), term()) -> {cerl:cerl(), term()}), + fun((cerl:cerl(), term()) -> {cerl:cerl(), term()}), + term(), cerl:cerl()) -> {cerl:cerl(), term()}. + +mapfold(Pre, Post, S00, T0) -> + {T, S0} = Pre(T0, S00), case type(T) of literal -> case concrete(T) of [_ | _] -> - {T1, S1} = mapfold(F, S0, cons_hd(T)), - {T2, S2} = mapfold(F, S1, cons_tl(T)), - F(update_c_cons(T, T1, T2), S2); + {T1, S1} = mapfold(Pre, Post, S0, cons_hd(T)), + {T2, S2} = mapfold(Pre, Post, S1, cons_tl(T)), + Post(update_c_cons(T, T1, T2), S2); V when tuple_size(V) > 0 -> - {Ts, S1} = mapfold_list(F, S0, tuple_es(T)), - F(update_c_tuple(T, Ts), S1); + {Ts, S1} = mapfold_list(Pre, Post, S0, tuple_es(T)), + Post(update_c_tuple(T, Ts), S1); _ -> - F(T, S0) + Post(T, S0) end; var -> - F(T, S0); + Post(T, S0); values -> - {Ts, S1} = mapfold_list(F, S0, values_es(T)), - F(update_c_values(T, Ts), S1); + {Ts, S1} = mapfold_list(Pre, Post, S0, values_es(T)), + Post(update_c_values(T, Ts), S1); cons -> - {T1, S1} = mapfold(F, S0, cons_hd(T)), - {T2, S2} = mapfold(F, S1, cons_tl(T)), - F(update_c_cons_skel(T, T1, T2), S2); + {T1, S1} = mapfold(Pre, Post, S0, cons_hd(T)), + {T2, S2} = mapfold(Pre, Post, S1, cons_tl(T)), + Post(update_c_cons_skel(T, T1, T2), S2); tuple -> - {Ts, S1} = mapfold_list(F, S0, tuple_es(T)), - F(update_c_tuple_skel(T, Ts), S1); + {Ts, S1} = mapfold_list(Pre, Post, S0, tuple_es(T)), + Post(update_c_tuple_skel(T, Ts), S1); map -> - {M , S1} = mapfold(F, S0, map_arg(T)), - {Ts, S2} = mapfold_list(F, S1, map_es(T)), - F(update_c_map(T, M, Ts), S2); + {M , S1} = mapfold(Pre, Post, S0, map_arg(T)), + {Ts, S2} = mapfold_list(Pre, Post, S1, map_es(T)), + Post(update_c_map(T, M, Ts), S2); map_pair -> - {Op, S1} = mapfold(F, S0, map_pair_op(T)), - {Key, S2} = mapfold(F, S1, map_pair_key(T)), - {Val, S3} = mapfold(F, S2, map_pair_val(T)), - F(update_c_map_pair(T,Op,Key,Val), S3); + {Op, S1} = mapfold(Pre, Post, S0, map_pair_op(T)), + {Key, S2} = mapfold(Pre, Post, S1, map_pair_key(T)), + {Val, S3} = mapfold(Pre, Post, S2, map_pair_val(T)), + Post(update_c_map_pair(T,Op,Key,Val), S3); 'let' -> - {Vs, S1} = mapfold_list(F, S0, let_vars(T)), - {A, S2} = mapfold(F, S1, let_arg(T)), - {B, S3} = mapfold(F, S2, let_body(T)), - F(update_c_let(T, Vs, A, B), S3); + {Vs, S1} = mapfold_list(Pre, Post, S0, let_vars(T)), + {A, S2} = mapfold(Pre, Post, S1, let_arg(T)), + {B, S3} = mapfold(Pre, Post, S2, let_body(T)), + Post(update_c_let(T, Vs, A, B), S3); seq -> - {A, S1} = mapfold(F, S0, seq_arg(T)), - {B, S2} = mapfold(F, S1, seq_body(T)), - F(update_c_seq(T, A, B), S2); + {A, S1} = mapfold(Pre, Post, S0, seq_arg(T)), + {B, S2} = mapfold(Pre, Post, S1, seq_body(T)), + Post(update_c_seq(T, A, B), S2); apply -> - {E, S1} = mapfold(F, S0, apply_op(T)), - {As, S2} = mapfold_list(F, S1, apply_args(T)), - F(update_c_apply(T, E, As), S2); + {E, S1} = mapfold(Pre, Post, S0, apply_op(T)), + {As, S2} = mapfold_list(Pre, Post, S1, apply_args(T)), + Post(update_c_apply(T, E, As), S2); call -> - {M, S1} = mapfold(F, S0, call_module(T)), - {N, S2} = mapfold(F, S1, call_name(T)), - {As, S3} = mapfold_list(F, S2, call_args(T)), - F(update_c_call(T, M, N, As), S3); + {M, S1} = mapfold(Pre, Post, S0, call_module(T)), + {N, S2} = mapfold(Pre, Post, S1, call_name(T)), + {As, S3} = mapfold_list(Pre, Post, S2, call_args(T)), + Post(update_c_call(T, M, N, As), S3); primop -> - {N, S1} = mapfold(F, S0, primop_name(T)), - {As, S2} = mapfold_list(F, S1, primop_args(T)), - F(update_c_primop(T, N, As), S2); + {N, S1} = mapfold(Pre, Post, S0, primop_name(T)), + {As, S2} = mapfold_list(Pre, Post, S1, primop_args(T)), + Post(update_c_primop(T, N, As), S2); 'case' -> - {A, S1} = mapfold(F, S0, case_arg(T)), - {Cs, S2} = mapfold_list(F, S1, case_clauses(T)), - F(update_c_case(T, A, Cs), S2); + {A, S1} = mapfold(Pre, Post, S0, case_arg(T)), + {Cs, S2} = mapfold_list(Pre, Post, S1, case_clauses(T)), + Post(update_c_case(T, A, Cs), S2); clause -> - {Ps, S1} = mapfold_list(F, S0, clause_pats(T)), - {G, S2} = mapfold(F, S1, clause_guard(T)), - {B, S3} = mapfold(F, S2, clause_body(T)), - F(update_c_clause(T, Ps, G, B), S3); + {Ps, S1} = mapfold_list(Pre, Post, S0, clause_pats(T)), + {G, S2} = mapfold(Pre, Post, S1, clause_guard(T)), + {B, S3} = mapfold(Pre, Post, S2, clause_body(T)), + Post(update_c_clause(T, Ps, G, B), S3); alias -> - {V, S1} = mapfold(F, S0, alias_var(T)), - {P, S2} = mapfold(F, S1, alias_pat(T)), - F(update_c_alias(T, V, P), S2); + {V, S1} = mapfold(Pre, Post, S0, alias_var(T)), + {P, S2} = mapfold(Pre, Post, S1, alias_pat(T)), + Post(update_c_alias(T, V, P), S2); 'fun' -> - {Vs, S1} = mapfold_list(F, S0, fun_vars(T)), - {B, S2} = mapfold(F, S1, fun_body(T)), - F(update_c_fun(T, Vs, B), S2); + {Vs, S1} = mapfold_list(Pre, Post, S0, fun_vars(T)), + {B, S2} = mapfold(Pre, Post, S1, fun_body(T)), + Post(update_c_fun(T, Vs, B), S2); 'receive' -> - {Cs, S1} = mapfold_list(F, S0, receive_clauses(T)), - {E, S2} = mapfold(F, S1, receive_timeout(T)), - {A, S3} = mapfold(F, S2, receive_action(T)), - F(update_c_receive(T, Cs, E, A), S3); + {Cs, S1} = mapfold_list(Pre, Post, S0, receive_clauses(T)), + {E, S2} = mapfold(Pre, Post, S1, receive_timeout(T)), + {A, S3} = mapfold(Pre, Post, S2, receive_action(T)), + Post(update_c_receive(T, Cs, E, A), S3); 'try' -> - {E, S1} = mapfold(F, S0, try_arg(T)), - {Vs, S2} = mapfold_list(F, S1, try_vars(T)), - {B, S3} = mapfold(F, S2, try_body(T)), - {Evs, S4} = mapfold_list(F, S3, try_evars(T)), - {H, S5} = mapfold(F, S4, try_handler(T)), - F(update_c_try(T, E, Vs, B, Evs, H), S5); + {E, S1} = mapfold(Pre, Post, S0, try_arg(T)), + {Vs, S2} = mapfold_list(Pre, Post, S1, try_vars(T)), + {B, S3} = mapfold(Pre, Post, S2, try_body(T)), + {Evs, S4} = mapfold_list(Pre, Post, S3, try_evars(T)), + {H, S5} = mapfold(Pre, Post, S4, try_handler(T)), + Post(update_c_try(T, E, Vs, B, Evs, H), S5); 'catch' -> - {B, S1} = mapfold(F, S0, catch_body(T)), - F(update_c_catch(T, B), S1); + {B, S1} = mapfold(Pre, Post, S0, catch_body(T)), + Post(update_c_catch(T, B), S1); binary -> - {Ds, S1} = mapfold_list(F, S0, binary_segments(T)), - F(update_c_binary(T, Ds), S1); + {Ds, S1} = mapfold_list(Pre, Post, S0, binary_segments(T)), + Post(update_c_binary(T, Ds), S1); bitstr -> - {Val, S1} = mapfold(F, S0, bitstr_val(T)), - {Size, S2} = mapfold(F, S1, bitstr_size(T)), - {Unit, S3} = mapfold(F, S2, bitstr_unit(T)), - {Type, S4} = mapfold(F, S3, bitstr_type(T)), - {Flags, S5} = mapfold(F, S4, bitstr_flags(T)), - F(update_c_bitstr(T, Val, Size, Unit, Type, Flags), S5); + {Val, S1} = mapfold(Pre, Post, S0, bitstr_val(T)), + {Size, S2} = mapfold(Pre, Post, S1, bitstr_size(T)), + {Unit, S3} = mapfold(Pre, Post, S2, bitstr_unit(T)), + {Type, S4} = mapfold(Pre, Post, S3, bitstr_type(T)), + {Flags, S5} = mapfold(Pre, Post, S4, bitstr_flags(T)), + Post(update_c_bitstr(T, Val, Size, Unit, Type, Flags), S5); letrec -> - {Ds, S1} = mapfold_pairs(F, S0, letrec_defs(T)), - {B, S2} = mapfold(F, S1, letrec_body(T)), - F(update_c_letrec(T, Ds, B), S2); + {Ds, S1} = mapfold_pairs(Pre, Post, S0, letrec_defs(T)), + {B, S2} = mapfold(Pre, Post, S1, letrec_body(T)), + Post(update_c_letrec(T, Ds, B), S2); module -> - {N, S1} = mapfold(F, S0, module_name(T)), - {Es, S2} = mapfold_list(F, S1, module_exports(T)), - {As, S3} = mapfold_pairs(F, S2, module_attrs(T)), - {Ds, S4} = mapfold_pairs(F, S3, module_defs(T)), - F(update_c_module(T, N, Es, As, Ds), S4) + {N, S1} = mapfold(Pre, Post, S0, module_name(T)), + {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) end. -mapfold_list(F, S0, [T | Ts]) -> - {T1, S1} = mapfold(F, S0, T), - {Ts1, S2} = mapfold_list(F, S1, Ts), +mapfold_list(Pre, Post, S0, [T | Ts]) -> + {T1, S1} = mapfold(Pre, Post, S0, T), + {Ts1, S2} = mapfold_list(Pre, Post, S1, Ts), {[T1 | Ts1], S2}; -mapfold_list(_, S, []) -> +mapfold_list(_, _, S, []) -> {[], S}. -mapfold_pairs(F, S0, [{T1, T2} | Ps]) -> - {T3, S1} = mapfold(F, S0, T1), - {T4, S2} = mapfold(F, S1, T2), - {Ps1, S3} = mapfold_pairs(F, S2, Ps), +mapfold_pairs(Pre, Post, S0, [{T1, T2} | Ps]) -> + {T3, S1} = mapfold(Pre, Post, S0, T1), + {T4, S2} = mapfold(Pre, Post, S1, T2), + {Ps1, S3} = mapfold_pairs(Pre, Post, S2, Ps), {[{T3, T4} | Ps1], S3}; -mapfold_pairs(_, S, []) -> +mapfold_pairs(_, _, S, []) -> {[], S}. @@ -640,8 +666,8 @@ vars_in_list([], _, A) -> vars_in_defs(Ds, S) -> vars_in_defs(Ds, S, []). -vars_in_defs([{_, F} | Ds], S, A) -> - vars_in_defs(Ds, S, ordsets:union(variables(F, S), A)); +vars_in_defs([{_, Post} | Ds], S, A) -> + vars_in_defs(Ds, S, ordsets:union(variables(Post, S), A)); vars_in_defs([], _, A) -> A. @@ -703,13 +729,14 @@ label(T, N, Env) -> %% Constant literals are not labeled. {T, N}; var -> - case dict:find(var_name(T), Env) of - {ok, L} -> - {As, _} = label_ann(T, L), - N1 = N; - error -> - {As, N1} = label_ann(T, N) - end, + {As, N1} = + case dict:find(var_name(T), Env) of + {ok, L} -> + {A, _} = label_ann(T, L), + {A, N}; + error -> + label_ann(T, N) + end, {set_ann(T, As), N1}; values -> {Ts, N1} = label_list(values_es(T), N, Env), diff --git a/lib/compiler/src/compile.erl b/lib/compiler/src/compile.erl index e0a29fe9b1..46917905de 100644 --- a/lib/compiler/src/compile.erl +++ b/lib/compiler/src/compile.erl @@ -40,6 +40,8 @@ %%---------------------------------------------------------------------- +-type abstract_code() :: [erl_parse:abstract_form()]. + -type option() :: atom() | {atom(), term()} | {'d', atom(), term()}. -type err_info() :: {erl_anno:line() | 'none', @@ -48,6 +50,9 @@ -type warnings() :: [{file:filename(), [err_info()]}]. -type mod_ret() :: {'ok', module()} | {'ok', module(), cerl:c_module()} %% with option 'to_core' + | {'ok', %% with option 'to_pp' + module() | [], %% module() if 'to_exp' + abstract_code()} | {'ok', module(), warnings()}. -type bin_ret() :: {'ok', module(), binary()} | {'ok', module(), binary(), warnings()}. @@ -78,7 +83,11 @@ file(File, Opts) when is_list(Opts) -> file(File, Opt) -> file(File, [Opt|?DEFAULT_OPTIONS]). -forms(File) -> forms(File, ?DEFAULT_OPTIONS). +-spec forms(abstract_code()) -> comp_ret(). + +forms(Forms) -> forms(Forms, ?DEFAULT_OPTIONS). + +-spec forms(abstract_code(), [option()] | option()) -> comp_ret(). forms(Forms, Opts) when is_list(Opts) -> do_compile({forms,Forms}, [binary|Opts++env_default_opts()]); @@ -106,6 +115,8 @@ noenv_file(File, Opts) when is_list(Opts) -> noenv_file(File, Opt) -> noenv_file(File, [Opt|?DEFAULT_OPTIONS]). +-spec noenv_forms(abstract_code(), [option()] | option()) -> comp_ret(). + noenv_forms(Forms, Opts) when is_list(Opts) -> do_compile({forms,Forms}, [binary|Opts]); noenv_forms(Forms, Opt) when is_atom(Opt) -> @@ -671,11 +682,16 @@ asm_passes() -> %% Assembly level optimisations. [{delay, [{pass,beam_a}, + {iff,da,{listing,"a"}}, {unless,no_postopt, - [{pass,beam_block}, + [{unless,no_reorder,{pass,beam_reorder}}, + {iff,dre,{listing,"reorder"}}, + {pass,beam_block}, {iff,dblk,{listing,"block"}}, {unless,no_except,{pass,beam_except}}, {iff,dexcept,{listing,"except"}}, + {unless,no_bs_opt,{pass,beam_bs}}, + {iff,dbs,{listing,"bs"}}, {unless,no_bopt,{pass,beam_bool}}, {iff,dbool,{listing,"bool"}}, {unless,no_topt,{pass,beam_type}}, @@ -703,6 +719,7 @@ asm_passes() -> {iff,no_postopt,[{pass,beam_clean}]}, {pass,beam_z}, + {iff,dz,{listing,"z"}}, {iff,dopt,{listing,"optimize"}}, {iff,'S',{listing,"S"}}, {iff,'to_asm',{done,"S"}}]}, @@ -1300,21 +1317,12 @@ generate_key(String) when is_list(String) -> encrypt({des3_cbc=Type,Key,IVec,BlockSize}, Bin0) -> Bin1 = case byte_size(Bin0) rem BlockSize of 0 -> Bin0; - N -> list_to_binary([Bin0,random_bytes(BlockSize-N)]) + N -> list_to_binary([Bin0,crypto:rand_bytes(BlockSize-N)]) end, Bin = crypto:block_encrypt(Type, Key, IVec, Bin1), TypeString = atom_to_list(Type), list_to_binary([0,length(TypeString),TypeString,Bin]). -random_bytes(N) -> - _ = random:seed(erlang:time_offset(), - erlang:monotonic_time(), - erlang:unique_integer()), - random_bytes_1(N, []). - -random_bytes_1(0, Acc) -> Acc; -random_bytes_1(N, Acc) -> random_bytes_1(N-1, [random:uniform(255)|Acc]). - save_core_code(St) -> {ok,St#compile{core_code=cerl:from_records(St#compile.code)}}. @@ -1612,11 +1620,8 @@ output_encoding(F, #compile{encoding = Encoding}) -> ok = io:setopts(F, [{encoding, Encoding}]), ok = io:fwrite(F, <<"%% ~s\n">>, [epp:encoding_to_string(Encoding)]). -restore_expanded_types("P", Fs) -> - epp:restore_typed_record_fields(Fs); restore_expanded_types("E", {M,I,Fs0}) -> - Fs1 = restore_expand_module(Fs0), - Fs = epp:restore_typed_record_fields(Fs1), + Fs = restore_expand_module(Fs0), {M,I,Fs}; restore_expanded_types(_Ext, Code) -> Code. @@ -1628,6 +1633,8 @@ restore_expand_module([{attribute,Line,spec,[Arg]}|Fs]) -> [{attribute,Line,spec,Arg}|restore_expand_module(Fs)]; restore_expand_module([{attribute,Line,callback,[Arg]}|Fs]) -> [{attribute,Line,callback,Arg}|restore_expand_module(Fs)]; +restore_expand_module([{attribute,Line,record,[R]}|Fs]) -> + [{attribute,Line,record,R}|restore_expand_module(Fs)]; restore_expand_module([F|Fs]) -> [F|restore_expand_module(Fs)]; restore_expand_module([]) -> []. diff --git a/lib/compiler/src/compiler.app.src b/lib/compiler/src/compiler.app.src index afb85f4710..a2b2a1d277 100644 --- a/lib/compiler/src/compiler.app.src +++ b/lib/compiler/src/compiler.app.src @@ -25,6 +25,7 @@ beam_asm, beam_block, beam_bool, + beam_bs, beam_bsm, beam_clean, beam_dead, @@ -37,6 +38,7 @@ beam_opcodes, beam_peep, beam_receive, + beam_reorder, beam_split, beam_trim, beam_type, diff --git a/lib/compiler/src/core_lib.erl b/lib/compiler/src/core_lib.erl index 3abb520485..839c736ff2 100644 --- a/lib/compiler/src/core_lib.erl +++ b/lib/compiler/src/core_lib.erl @@ -21,52 +21,16 @@ -module(core_lib). --deprecated({get_anno,1,next_major_release}). --deprecated({set_anno,2,next_major_release}). --deprecated({is_literal,1,next_major_release}). --deprecated({is_literal_list,1,next_major_release}). --deprecated({literal_value,1,next_major_release}). - --export([get_anno/1,set_anno/2]). --export([is_literal/1,is_literal_list/1]). --export([literal_value/1]). -export([make_values/1]). -export([is_var_used/2]). -include("core_parse.hrl"). -%% -%% Generic get/set annotation that should be used only with cerl() structures. -%% --spec get_anno(cerl:cerl()) -> term(). - -get_anno(C) -> cerl:get_ann(C). - --spec set_anno(cerl:cerl(), term()) -> cerl:cerl(). - -set_anno(C, A) -> cerl:set_ann(C, A). - --spec is_literal(cerl:cerl()) -> boolean(). - -is_literal(Cerl) -> - cerl:is_literal(cerl:fold_literal(Cerl)). - --spec is_literal_list([cerl:cerl()]) -> boolean(). - -is_literal_list(Es) -> lists:all(fun is_literal/1, Es). - -%% Return the value of LitExpr. --spec literal_value(cerl:c_literal() | cerl:c_binary() | - cerl:c_map() | cerl:c_cons() | cerl:c_tuple()) -> term(). - -literal_value(Cerl) -> - cerl:concrete(cerl:fold_literal(Cerl)). - %% Make a suitable values structure, expr or values, depending on Expr. -spec make_values([cerl:cerl()] | cerl:cerl()) -> cerl:cerl(). make_values([E]) -> E; -make_values([H|_]=Es) -> #c_values{anno=get_anno(H),es=Es}; +make_values([H|_]=Es) -> #c_values{anno=cerl:get_ann(H),es=Es}; make_values([]) -> #c_values{es=[]}; make_values(E) -> E. diff --git a/lib/compiler/src/core_lint.erl b/lib/compiler/src/core_lint.erl index cc54f6e411..7d3513c0ba 100644 --- a/lib/compiler/src/core_lint.erl +++ b/lib/compiler/src/core_lint.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1999-2013. All Rights Reserved. +%% Copyright Ericsson AB 1999-2015. All Rights Reserved. %% %% Licensed under the Apache License, Version 2.0 (the "License"); %% you may not use this file except in compliance with the License. @@ -73,7 +73,7 @@ %% Define the lint state record. -record(lint, {module :: module(), % Current module - func :: fa(), % Current function + func :: fa() | 'undefined', % Current function errors = [] :: [error()], % Errors warnings= [] :: [warning()]}). % Warnings diff --git a/lib/compiler/src/rec_env.erl b/lib/compiler/src/rec_env.erl index 0e9e12d1ad..5a4a870769 100644 --- a/lib/compiler/src/rec_env.erl +++ b/lib/compiler/src/rec_env.erl @@ -598,7 +598,16 @@ start_range(Env) -> %% (pseudo-)randomly distributed over the range. generate(_N, Range) -> - random:uniform(Range). % works well + %% We must use the same sequence of random variables to ensure + %% that two compilations of the same source code generates the + %% same BEAM code. + case rand:export_seed() of + undefined -> + rand:seed(exsplus, {1,42,2053}); + _ -> + ok + end, + rand:uniform(Range). % works well %% ===================================================================== diff --git a/lib/compiler/src/sys_core_dsetel.erl b/lib/compiler/src/sys_core_dsetel.erl index ac32db10fe..c6cfdbae7e 100644 --- a/lib/compiler/src/sys_core_dsetel.erl +++ b/lib/compiler/src/sys_core_dsetel.erl @@ -72,7 +72,7 @@ module(M0, _Options) -> {ok,M}. visit_module(#c_module{defs=Ds0}=R) -> - Env = dict:new(), + Env = #{}, Ds = visit_module_1(Ds0, Env, []), R#c_module{defs=Ds}. @@ -95,9 +95,11 @@ visit(Env, #c_var{name={_,_}}=R) -> {R, Env}; visit(Env0, #c_var{name=X}=R) -> %% There should not be any free variables. If there are, - %% the next line will cause an exception. - {ok, N} = dict:find(X, Env0), - {R, dict:store(X, N+1, Env0)}; + %% the case will fail with an exception. + case Env0 of + #{X:=N} -> + {R, Env0#{X:=N+1}} + end; visit(Env, #c_literal{}=R) -> {R, Env}; visit(Env0, #c_tuple{es=Es0}=R) -> @@ -203,7 +205,7 @@ bind_vars(Vs, Env) -> bind_vars(Vs, Env, []). bind_vars([#c_var{name=X}|Vs], Env0, Xs)-> - bind_vars(Vs, dict:store(X, 0, Env0), [X|Xs]); + bind_vars(Vs, Env0#{X=>0}, [X|Xs]); bind_vars([], Env,Xs) -> {Xs, Env}. @@ -217,7 +219,7 @@ visit_pats([], Env, Vs) -> {Vs, Env}. visit_pat(Env0, #c_var{name=V}, Vs) -> - {[V|Vs], dict:store(V, 0, Env0)}; + {[V|Vs], Env0#{V=>0}}; visit_pat(Env0, #c_tuple{es=Es}, Vs) -> visit_pats(Es, Env0, Vs); visit_pat(Env0, #c_map{es=Es}, Vs) -> @@ -235,23 +237,25 @@ visit_pat(Env0, #c_bitstr{val=Val,size=Sz}, Vs0) -> case Sz of #c_var{name=V} -> %% We don't tolerate free variables. - {ok, N} = dict:find(V, Env0), - {Vs0, dict:store(V, N+1, Env0)}; + case Env0 of + #{V:=N} -> + {Vs0, Env0#{V:=N+1}} + end; _ -> visit_pat(Env0, Sz, Vs0) end, visit_pat(Env1, Val, Vs1); visit_pat(Env0, #c_alias{pat=P,var=#c_var{name=V}}, Vs) -> - visit_pat(dict:store(V, 0, Env0), P, [V|Vs]); + visit_pat(Env0#{V=>0}, P, [V|Vs]); visit_pat(Env, #c_literal{}, Vs) -> {Vs, Env}. restore_vars([V|Vs], Env0, Env1) -> - case dict:find(V, Env0) of - {ok, N} -> - restore_vars(Vs, Env0, dict:store(V, N, Env1)); - error -> - restore_vars(Vs, Env0, dict:erase(V, Env1)) + case Env0 of + #{V:=N} -> + restore_vars(Vs, Env0, Env1#{V=>N}); + _ -> + restore_vars(Vs, Env0, maps:remove(V, Env1)) end; restore_vars([], _, Env1) -> Env1. @@ -349,8 +353,8 @@ is_safe(#c_literal{}) -> true; is_safe(_) -> false. is_single_use(V, Env) -> - case dict:find(V, Env) of - {ok, 1} -> + case Env of + #{V:=1} -> true; _ -> false diff --git a/lib/compiler/src/sys_core_fold.erl b/lib/compiler/src/sys_core_fold.erl index 65699ccda9..ab67c8164b 100644 --- a/lib/compiler/src/sys_core_fold.erl +++ b/lib/compiler/src/sys_core_fold.erl @@ -277,7 +277,7 @@ expr(#c_fun{}=Fun, effect, _) -> add_warning(Fun, useless_building), void(); expr(#c_fun{vars=Vs0,body=B0}=Fun, Ctxt0, Sub0) -> - {Vs1,Sub1} = pattern_list(Vs0, Sub0), + {Vs1,Sub1} = var_list(Vs0, Sub0), Ctxt = case Ctxt0 of {letrec,Ctxt1} -> Ctxt1; value -> value @@ -420,13 +420,13 @@ expr(#c_try{anno=A,arg=E0,vars=Vs0,body=B0,evars=Evs0,handler=H0}=Try, _, Sub0) %% Here is the general try/catch construct outside of guards. %% We can remove try if the value is simple and replace it with a let. E1 = body(E0, value, Sub0), - {Vs1,Sub1} = pattern_list(Vs0, Sub0), + {Vs1,Sub1} = var_list(Vs0, Sub0), B1 = body(B0, value, Sub1), case is_safe_simple(E1, Sub0) of true -> expr(#c_let{anno=A,vars=Vs1,arg=E1,body=B1}, value, Sub0); false -> - {Evs1,Sub2} = pattern_list(Evs0, 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. @@ -1078,15 +1078,28 @@ is_atom_or_var(_) -> false. %% clause(Clause, Cepxr, Context, Sub) -> Clause. -clause(#c_clause{pats=Ps0,guard=G0,body=B0}=Cl, Cexpr, Ctxt, Sub0) -> - {Ps1,Sub1} = pattern_list(Ps0, Sub0), +clause(#c_clause{pats=Ps0}=Cl, Cexpr, Ctxt, Sub0) -> + try pattern_list(Ps0, Sub0) of + {Ps1,Sub1} -> + clause_1(Cl, Ps1, Cexpr, Ctxt, Sub1) + catch + nomatch -> + Cl#c_clause{anno=[compiler_generated], + guard=#c_literal{val=false}} + end. + +clause_1(#c_clause{guard=G0,body=B0}=Cl, Ps1, Cexpr, Ctxt, Sub1) -> Sub2 = update_types(Cexpr, Ps1, Sub1), - GSub = case {Cexpr,Ps1} of - {#c_var{name='_'},_} -> + GSub = case {Cexpr,Ps1,G0} of + {_,_,#c_literal{}} -> + %% No need for substitution tricks when the guard + %% does not contain any variables. + Sub2; + {#c_var{name='_'},_,_} -> %% In a 'receive', Cexpr is the variable '_', which represents the %% message being matched. We must NOT do any extra substiutions. Sub2; - {#c_var{},[#c_var{}=Var]} -> + {#c_var{},[#c_var{}=Var],_} -> %% The idea here is to optimize expressions such as %% %% case A of A -> ... @@ -1120,7 +1133,7 @@ clause(#c_clause{pats=Ps0,guard=G0,body=B0}=Cl, Cexpr, Ctxt, Sub0) -> %% the unsubstituted variables and values. let_substs(Vs0, As0, Sub0) -> - {Vs1,Sub1} = pattern_list(Vs0, Sub0), + {Vs1,Sub1} = var_list(Vs0, Sub0), {Vs2,As1,Ss} = let_substs_1(Vs1, As0, Sub1), Sub2 = sub_add_scope([V || #c_var{name=V} <- Vs2], Sub1), {Vs2,As1, @@ -1206,20 +1219,132 @@ bin_pattern_list(Ps0, Isub, Osub0) -> {Ps,{_,Osub}} = mapfoldl(fun bin_pattern/2, {Isub,Osub0}, Ps0), {Ps,Osub}. -bin_pattern(#c_bitstr{val=E0,size=Size0}=Pat, {Isub0,Osub0}) -> +bin_pattern(#c_bitstr{val=E0,size=Size0}=Pat0, {Isub0,Osub0}) -> Size1 = expr(Size0, Isub0), {E1,Osub} = pattern(E0, Isub0, Osub0), Isub = case E0 of #c_var{} -> sub_set_var(E0, E1, Isub0); _ -> Isub0 end, - {Pat#c_bitstr{val=E1,size=Size1},{Isub,Osub}}. + Pat = Pat0#c_bitstr{val=E1,size=Size1}, + bin_pat_warn(Pat), + {Pat,{Isub,Osub}}. pattern_list(Ps, Sub) -> pattern_list(Ps, Sub, Sub). pattern_list(Ps0, Isub, Osub0) -> mapfoldl(fun (P, Osub) -> pattern(P, Isub, Osub) end, Osub0, Ps0). +%% var_list([Var], InSub) -> {Pattern,OutSub}. +%% Works like pattern_list/2 but only accept variables and is +%% guaranteed not to throw an exception. + +var_list(Vs, Sub0) -> + mapfoldl(fun (#c_var{}=V, Sub) -> + pattern(V, Sub, Sub) + end, Sub0, Vs). + + +%%% +%%% Generate warnings for binary patterns that will not match. +%%% + +bin_pat_warn(#c_bitstr{type=#c_literal{val=Type}, + val=Val0, + size=#c_literal{val=Sz}, + unit=#c_literal{val=Unit}, + flags=Fl}=Pat) -> + case {Type,Sz} of + {_,_} when is_integer(Sz), Sz >= 0 -> ok; + {binary,all} -> ok; + {utf8,undefined} -> ok; + {utf16,undefined} -> ok; + {utf32,undefined} -> ok; + {_,_} -> + add_warning(Pat, {nomatch_bit_syntax_size,Sz}), + throw(nomatch) + end, + case {Type,Val0} of + {integer,#c_literal{val=Val}} when is_integer(Val) -> + Signedness = signedness(Fl), + TotalSz = Sz * Unit, + bit_pat_warn_int(Val, TotalSz, Signedness, Pat); + {float,#c_literal{val=Val}} when is_float(Val) -> + ok; + {utf8,#c_literal{val=Val}} when is_integer(Val) -> + bit_pat_warn_unicode(Val, Pat); + {utf16,#c_literal{val=Val}} when is_integer(Val) -> + bit_pat_warn_unicode(Val, Pat); + {utf32,#c_literal{val=Val}} when is_integer(Val) -> + bit_pat_warn_unicode(Val, Pat); + {_,#c_literal{val=Val}} -> + add_warning(Pat, {nomatch_bit_syntax_type,Val,Type}), + throw(nomatch); + {_,_} -> + ok + end; +bin_pat_warn(#c_bitstr{type=#c_literal{val=Type},val=Val0,flags=Fl}=Pat) -> + %% Size is variable. Not much that we can check. + case {Type,Val0} of + {integer,#c_literal{val=Val}} when is_integer(Val) -> + case signedness(Fl) of + unsigned when Val < 0 -> + add_warning(Pat, {nomatch_bit_syntax_unsigned,Val}), + throw(nomatch); + _ -> + ok + end; + {float,#c_literal{val=Val}} when is_float(Val) -> + ok; + {_,#c_literal{val=Val}} -> + add_warning(Pat, {nomatch_bit_syntax_type,Val,Type}), + throw(nomatch); + {_,_} -> + ok + end. + +bit_pat_warn_int(Val, 0, signed, Pat) -> + if + Val =:= 0 -> + ok; + true -> + add_warning(Pat, {nomatch_bit_syntax_truncated,signed,Val,0}), + throw(nomatch) + end; +bit_pat_warn_int(Val, Sz, signed, Pat) -> + if + Val < 0, Val bsr (Sz - 1) =/= -1 -> + add_warning(Pat, {nomatch_bit_syntax_truncated,signed,Val,Sz}), + throw(nomatch); + Val > 0, Val bsr (Sz - 1) =/= 0 -> + add_warning(Pat, {nomatch_bit_syntax_truncated,signed,Val,Sz}), + throw(nomatch); + true -> + ok + end; +bit_pat_warn_int(Val, _Sz, unsigned, Pat) when Val < 0 -> + add_warning(Pat, {nomatch_bit_syntax_unsigned,Val}), + throw(nomatch); +bit_pat_warn_int(Val, Sz, unsigned, Pat) -> + if + Val bsr Sz =:= 0 -> + ok; + true -> + add_warning(Pat, {nomatch_bit_syntax_truncated,unsigned,Val,Sz}), + throw(nomatch) + end. + +bit_pat_warn_unicode(U, _Pat) when 0 =< U, U =< 16#10FFFF -> + ok; +bit_pat_warn_unicode(U, Pat) -> + add_warning(Pat, {nomatch_bit_syntax_unicode,U}), + throw(nomatch). + +signedness(#c_literal{val=Flags}) -> + [S] = [F || F <- Flags, F =:= signed orelse F =:= unsigned], + S. + + %% is_subst(Expr) -> true | false. %% Test whether an expression is a suitable substitution. @@ -2251,11 +2376,11 @@ move_let_into_expr(#c_let{vars=InnerVs0,body=InnerBody0}=Inner, %% Arg = body(Arg0, Sub0), ScopeSub0 = sub_subst_scope(Sub0#sub{t=#{}}), - {OuterVs,ScopeSub} = pattern_list(OuterVs0, ScopeSub0), + {OuterVs,ScopeSub} = var_list(OuterVs0, ScopeSub0), OuterBody = body(OuterBody0, ScopeSub), - {InnerVs,Sub} = pattern_list(InnerVs0, Sub0), + {InnerVs,Sub} = var_list(InnerVs0, Sub0), InnerBody = body(InnerBody0, Sub), Outer#c_let{vars=OuterVs,arg=Arg, body=Inner#c_let{vars=InnerVs,arg=OuterBody,body=InnerBody}}; @@ -2271,39 +2396,49 @@ move_let_into_expr(#c_let{vars=Lvs0,body=Lbody0}=Let, case {TwoClauses,is_failing_clause(Ca0),is_failing_clause(Cb0)} of {true,false,true} -> %% let <Lvars> = case <Case-expr> of - %% <Cvars> -> <Clause-body>; - %% <OtherCvars> -> erlang:error(...) + %% <Cpats> -> <Clause-body>; + %% <OtherCpats> -> erlang:error(...) %% end %% in <Let-body> %% %% ==> %% %% case <Case-expr> of - %% <Cvars> -> + %% <Cpats> -> %% let <Lvars> = <Clause-body> %% in <Let-body>; - %% <OtherCvars> -> erlang:error(...) + %% <OtherCpats> -> erlang:error(...) %% end Cexpr = body(Cexpr0, Sub0), - CaVars0 = Ca0#c_clause.pats, + CaPats0 = Ca0#c_clause.pats, G0 = Ca0#c_clause.guard, B0 = Ca0#c_clause.body, ScopeSub0 = sub_subst_scope(Sub0#sub{t=#{}}), - {CaVars,ScopeSub} = pattern_list(CaVars0, ScopeSub0), - G = guard(G0, ScopeSub), - - B1 = body(B0, ScopeSub), - - {Lvs,B2,Sub1} = let_substs(Lvs0, B1, Sub0), - Sub2 = Sub1#sub{s=cerl_sets:union(ScopeSub#sub.s, - Sub1#sub.s)}, - Lbody = body(Lbody0, Sub2), - B = Let#c_let{vars=Lvs,arg=core_lib:make_values(B2),body=Lbody}, - - Ca = Ca0#c_clause{pats=CaVars,guard=G,body=B}, - Cb = clause(Cb0, Cexpr, value, Sub0), - Case#c_case{arg=Cexpr,clauses=[Ca,Cb]}; + try pattern_list(CaPats0, ScopeSub0) of + {CaPats,ScopeSub} -> + G = guard(G0, ScopeSub), + + B1 = body(B0, ScopeSub), + + {Lvs,B2,Sub1} = let_substs(Lvs0, B1, Sub0), + Sub2 = Sub1#sub{s=cerl_sets:union(ScopeSub#sub.s, + Sub1#sub.s)}, + Lbody = body(Lbody0, Sub2), + B = Let#c_let{vars=Lvs, + arg=core_lib:make_values(B2), + body=Lbody}, + + Ca = Ca0#c_clause{pats=CaPats,guard=G,body=B}, + Cb = clause(Cb0, Cexpr, value, Sub0), + Case#c_case{arg=Cexpr,clauses=[Ca,Cb]} + catch + nomatch -> + %% This is not a defeat. The code will eventually + %% be optimized to erlang:error(...) by the other + %% optimizations done in this module. + impossible + end; {_,_,_} -> impossible end; move_let_into_expr(#c_let{vars=Lvs0,body=Lbody0}=Let, @@ -2595,7 +2730,7 @@ move_case_into_arg(#c_case{arg=#c_let{vars=OuterVars0,arg=OuterArg, %% in case <InnerArg> of <InnerClauses> end %% ScopeSub0 = sub_subst_scope(Sub#sub{t=#{}}), - {OuterVars,ScopeSub} = pattern_list(OuterVars0, ScopeSub0), + {OuterVars,ScopeSub} = var_list(OuterVars0, ScopeSub0), InnerArg = body(InnerArg0, ScopeSub), Outer#c_let{vars=OuterVars,arg=OuterArg, body=Inner#c_case{arg=InnerArg,clauses=InnerClauses}}; @@ -2624,14 +2759,18 @@ move_case_into_arg(#c_case{arg=#c_case{arg=OuterArg, %% end %% ScopeSub0 = sub_subst_scope(Sub#sub{t=#{}}), - {OuterPats,ScopeSub} = pattern_list(OuterPats0, ScopeSub0), - OuterGuard = guard(OuterGuard0, ScopeSub), - InnerArg = body(InnerArg0, ScopeSub), - Inner = Inner0#c_case{arg=InnerArg,clauses=InnerClauses}, - OuterCa = OuterCa0#c_clause{pats=OuterPats,guard=OuterGuard, - body=Inner}, - Outer#c_case{arg=OuterArg, - clauses=[OuterCa,OuterCb]}; + + %% We KNOW that pattern_list/2 has already been called for OuterPats0; + %% therefore, it cannot throw an exception. + {OuterPats,ScopeSub} = pattern_list(OuterPats0, ScopeSub0), + OuterGuard = guard(OuterGuard0, ScopeSub), + InnerArg = body(InnerArg0, ScopeSub), + Inner = Inner0#c_case{arg=InnerArg,clauses=InnerClauses}, + OuterCa = OuterCa0#c_clause{pats=OuterPats, + guard=OuterGuard, + body=Inner}, + Outer#c_case{arg=OuterArg, + clauses=[OuterCa,OuterCb]}; false -> impossible end; @@ -2793,12 +2932,18 @@ extract_type_1(Expr, Sub) -> true -> bool end. +returns_integer('band', [_,_]) -> true; +returns_integer('bnot', [_]) -> true; +returns_integer('bor', [_,_]) -> true; +returns_integer('bxor', [_,_]) -> true; returns_integer(bit_size, [_]) -> true; returns_integer('bsl', [_,_]) -> true; returns_integer('bsr', [_,_]) -> true; returns_integer(byte_size, [_]) -> true; +returns_integer('div', [_,_]) -> true; returns_integer(length, [_]) -> true; returns_integer('rem', [_,_]) -> true; +returns_integer('round', [_]) -> true; returns_integer(size, [_]) -> true; returns_integer(tuple_size, [_]) -> true; returns_integer(trunc, [_]) -> true; @@ -3207,6 +3352,29 @@ format_error(nomatch_shadow) -> "this clause cannot match because a previous clause always matches"; format_error(nomatch_guard) -> "the guard for this clause evaluates to 'false'"; +format_error({nomatch_bit_syntax_truncated,Signess,Val,Sz}) -> + S = case Signess of + signed -> "a 'signed'"; + unsigned -> "an 'unsigned'" + end, + F = "this clause cannot match because the value ~P" + " will not fit in ~s binary segment of size ~p", + flatten(io_lib:format(F, [Val,10,S,Sz])); +format_error({nomatch_bit_syntax_unsigned,Val}) -> + F = "this clause cannot match because the negative value ~P" + " will never match the value of an 'unsigned' binary segment", + flatten(io_lib:format(F, [Val,10])); +format_error({nomatch_bit_syntax_size,Sz}) -> + F = "this clause cannot match because '~P' is not a valid size for a binary segment", + flatten(io_lib:format(F, [Sz,10])); +format_error({nomatch_bit_syntax_type,Val,Type}) -> + F = "this clause cannot match because '~P' is not of the" + " expected type '~p'", + flatten(io_lib:format(F, [Val,10,Type])); +format_error({nomatch_bit_syntax_unicode,Val}) -> + F = "this clause cannot match because the value ~p" + " is not a valid Unicode code point", + flatten(io_lib:format(F, [Val])); format_error(no_clause_match) -> "no clause will ever match"; format_error(nomatch_clause_type) -> diff --git a/lib/compiler/src/sys_pre_expand.erl b/lib/compiler/src/sys_pre_expand.erl index d9cc4b530c..7ab4e1845c 100644 --- a/lib/compiler/src/sys_pre_expand.erl +++ b/lib/compiler/src/sys_pre_expand.erl @@ -29,30 +29,26 @@ %% Main entry point. -export([module/2]). --import(ordsets, [from_list/1,union/2]). -import(lists, [member/2,foldl/3,foldr/3]). --include("../include/erl_bits.hrl"). - -type fa() :: {atom(), arity()}. -record(expand, {module=[], %Module name exports=[], %Exports - imports=[], %Imports attributes=[], %Attributes callbacks=[], %Callbacks optional_callbacks=[] :: [fa()], %Optional callbacks - defined, %Defined functions (gb_set) vcount=0, %Variable counter func=[], %Current function arity=[], %Arity for current function - fcount=0 %Local fun count + fcount=0, %Local fun count + ctype %Call type map }). %% module(Forms, CompileOptions) %% {ModuleName,Exports,TransformedForms,CompileOptions'} -%% Expand the forms in one module. N.B.: the lists of predefined -%% exports and imports are really ordsets! +%% Expand the forms in one module. +%% %% CompileOptions is augmented with options from -compile attributes. module(Fs0, Opts0) -> @@ -65,19 +61,28 @@ module(Fs0, Opts0) -> %% Set pre-defined exported functions. PreExp = [{module_info,0},{module_info,1}], + %% Build the set of defined functions and the initial call + %% type map. + Defined = defined_functions(Fs, PreExp), + Ctype = maps:from_list([{K,local} || K <- Defined]), + %% Build initial expand record. St0 = #expand{exports=PreExp, - defined=PreExp + ctype=Ctype }, + %% Expand the functions. - {Tfs,St1} = forms(Fs, define_functions(Fs, St0)), + {Tfs,St1} = forms(Fs, St0), + %% Get the correct list of exported functions. Exports = case member(export_all, Opts) of - true -> gb_sets:to_list(St1#expand.defined); + true -> Defined; false -> St1#expand.exports end, + St2 = St1#expand{exports=Exports,ctype=undefined}, + %% Generate all functions from stored info. - {Ats,St3} = module_attrs(St1#expand{exports = Exports}), + {Ats,St3} = module_attrs(St2), {Mfs,St4} = module_predef_funcs(St3), {St4#expand.module, St4#expand.exports, Ats ++ Tfs ++ Mfs, Opts}. @@ -85,14 +90,14 @@ module(Fs0, Opts0) -> compiler_options(Forms) -> lists:flatten([C || {attribute,_,compile,C} <- Forms]). -%% define_function(Form, State) -> State. +%% defined_function(Forms, Predef) -> Functions. %% Add function to defined if form is a function. -define_functions(Forms, #expand{defined=Predef}=St) -> +defined_functions(Forms, Predef) -> Fs = foldl(fun({function,_,N,A,_Cs}, Acc) -> [{N,A}|Acc]; (_, Acc) -> Acc end, Predef, Forms), - St#expand{defined=gb_sets:from_list(Fs)}. + ordsets:from_list(Fs). module_attrs(#expand{attributes=Attributes}=St) -> Attrs = [{attribute,Line,Name,Val} || {Name,Line,Val} <- Attributes], @@ -113,23 +118,21 @@ is_fa_list([{FuncName, Arity}|L]) is_fa_list([]) -> true; is_fa_list(_) -> false. -module_predef_funcs(St) -> - {Mpf1,St1}=module_predef_func_beh_info(St), - {Mpf2,St2}=module_predef_funcs_mod_info(St1), +module_predef_funcs(St0) -> + {Mpf1,St1} = module_predef_func_beh_info(St0), + Mpf2 = module_predef_funcs_mod_info(St1), Mpf = [erl_parse:new_anno(F) || F <- Mpf1++Mpf2], - {Mpf,St2}. + {Mpf,St1}. module_predef_func_beh_info(#expand{callbacks=[]}=St) -> {[], St}; module_predef_func_beh_info(#expand{callbacks=Callbacks, optional_callbacks=OptionalCallbacks, - defined=Defined, exports=Exports}=St) -> - PreDef=[{behaviour_info,1}], - PreExp=PreDef, + PreDef0 = [{behaviour_info,1}], + PreDef = ordsets:from_list(PreDef0), {[gen_beh_info(Callbacks, OptionalCallbacks)], - St#expand{defined=gb_sets:union(gb_sets:from_list(PreDef), Defined), - exports=union(from_list(PreExp), Exports)}}. + St#expand{exports=ordsets:union(PreDef, Exports)}}. gen_beh_info(Callbacks, OptionalCallbacks) -> List = make_list(Callbacks), @@ -156,20 +159,16 @@ make_optional_list([{Name,Arity}|Rest]) -> {integer,0,Arity}]}, make_optional_list(Rest)}. -module_predef_funcs_mod_info(St) -> - PreDef = [{module_info,0},{module_info,1}], - PreExp = PreDef, - {[{function,0,module_info,0, - [{clause,0,[],[], +module_predef_funcs_mod_info(#expand{module=Mod}) -> + ModAtom = {atom,0,Mod}, + [{function,0,module_info,0, + [{clause,0,[],[], [{call,0,{remote,0,{atom,0,erlang},{atom,0,get_module_info}}, - [{atom,0,St#expand.module}]}]}]}, - {function,0,module_info,1, - [{clause,0,[{var,0,'X'}],[], + [ModAtom]}]}]}, + {function,0,module_info,1, + [{clause,0,[{var,0,'X'}],[], [{call,0,{remote,0,{atom,0,erlang},{atom,0,get_module_info}}, - [{atom,0,St#expand.module},{var,0,'X'}]}]}]}], - St#expand{defined=gb_sets:union(gb_sets:from_list(PreDef), - St#expand.defined), - exports=union(from_list(PreExp), St#expand.exports)}}. + [ModAtom,{var,0,'X'}]}]}]}]. %% forms(Forms, State) -> %% {TransformedForms,State'} @@ -196,7 +195,8 @@ attribute(module, Module, _L, St) -> true = is_atom(Module), St#expand{module=Module}; attribute(export, Es, _L, St) -> - St#expand{exports=union(from_list(Es), St#expand.exports)}; + St#expand{exports=ordsets:union(ordsets:from_list(Es), + St#expand.exports)}; attribute(import, Is, _L, St) -> import(Is, St); attribute(compile, _C, _L, St) -> @@ -231,8 +231,6 @@ head(As, St) -> pattern_list(As, St). %% {TransformedPattern,State'} %% -pattern({var,_,'_'}=Var, St) -> %Ignore anonymous variable. - {Var,St}; pattern({var,_,_}=Var, St) -> {Var,St}; pattern({char,_,_}=Char, St) -> @@ -385,19 +383,19 @@ expr({block,Line,Es0}, St0) -> {Es,St1} = exprs(Es0, St0), {{block,Line,Es},St1}; expr({'if',Line,Cs0}, St0) -> - {Cs,St1} = icr_clauses(Cs0, St0), + {Cs,St1} = clauses(Cs0, St0), {{'if',Line,Cs},St1}; expr({'case',Line,E0,Cs0}, St0) -> {E,St1} = expr(E0, St0), - {Cs,St2} = icr_clauses(Cs0, St1), + {Cs,St2} = clauses(Cs0, St1), {{'case',Line,E,Cs},St2}; expr({'receive',Line,Cs0}, St0) -> - {Cs,St1} = icr_clauses(Cs0, St0), + {Cs,St1} = clauses(Cs0, St0), {{'receive',Line,Cs},St1}; expr({'receive',Line,Cs0,To0,ToEs0}, St0) -> {To,St1} = expr(To0, St0), {ToEs,St2} = exprs(ToEs0, St1), - {Cs,St3} = icr_clauses(Cs0, St2), + {Cs,St3} = clauses(Cs0, St2), {{'receive',Line,Cs,To,ToEs},St3}; expr({'fun',Line,Body}, St) -> fun_tq(Line, Body, St); @@ -406,21 +404,15 @@ expr({named_fun,Line,Name,Cs}, St) -> expr({call,Line,{atom,La,N}=Atom,As0}, St0) -> {As,St1} = expr_list(As0, St0), Ar = length(As), - case defined(N,Ar,St1) of - true -> + Key = {N,Ar}, + case St1#expand.ctype of + #{Key:=local} -> {{call,Line,Atom,As},St1}; + #{Key:={imported,Mod}} -> + {{call,Line,{remote,La,{atom,La,Mod},Atom},As},St1}; _ -> - case imported(N, Ar, St1) of - {yes,Mod} -> - {{call,Line,{remote,La,{atom,La,Mod},Atom},As},St1}; - no -> - case erl_internal:bif(N, Ar) of - true -> - {{call,Line,{remote,La,{atom,La,erlang},Atom},As},St1}; - false -> %% This should have been handled by erl_lint - {{call,Line,Atom,As},St1} - end - end + true = erl_internal:bif(N, Ar), + {{call,Line,{remote,La,{atom,La,erlang},Atom},As},St1} end; expr({call,Line,{remote,Lr,M0,F},As0}, St0) -> {[M1,F1|As1],St1} = expr_list([M0,F|As0], St0), @@ -430,12 +422,11 @@ expr({call,Line,F,As0}, St0) -> {{call,Line,Fun1,As1},St1}; expr({'try',Line,Es0,Scs0,Ccs0,As0}, St0) -> {Es1,St1} = exprs(Es0, St0), - {Scs1,St2} = icr_clauses(Scs0, St1), - {Ccs1,St3} = icr_clauses(Ccs0, St2), + {Scs1,St2} = clauses(Scs0, St1), + {Ccs1,St3} = clauses(Ccs0, St2), {As1,St4} = exprs(As0, St3), {{'try',Line,Es1,Scs1,Ccs1,As1},St4}; expr({'catch',Line,E0}, St0) -> - %% Catch exports no new variables. {E,St1} = expr(E0, St0), {{'catch',Line,E},St1}; expr({match,Line,P0,E0}, St0) -> @@ -456,21 +447,6 @@ expr_list([E0|Es0], St0) -> {[E|Es],St2}; expr_list([], St) -> {[],St}. -%% icr_clauses([Clause], State) -> {[TransformedClause],State'} -%% Be very careful here to return the variables that are really used -%% and really new. - -icr_clauses([], St) -> {[],St}; -icr_clauses(Clauses, St) -> icr_clauses2(Clauses, St). - -icr_clauses2([{clause,Line,H0,G0,B0}|Cs0], St0) -> - {H,St1} = head(H0, St0), - {G,St2} = guard(G0, St1), - {B,St3} = exprs(B0, St2), - {Cs,St4} = icr_clauses2(Cs0, St3), - {[{clause,Line,H,G,B}|Cs],St4}; -icr_clauses2([], St) -> {[],St}. - %% lc_tq(Line, Qualifiers, State) -> %% {[TransQual],State'} @@ -486,16 +462,9 @@ lc_tq(Line, [{b_generate,Lg,P0,G0}|Qs0], St0) -> {Qs1,St3} = lc_tq(Line, Qs0, St2), {[{b_generate,Lg,P1,G1}|Qs1],St3}; lc_tq(Line, [F0 | Qs0], St0) -> - case erl_lint:is_guard_test(F0) of - true -> - {F1,St1} = guard_test(F0, St0), - {Qs1,St2} = lc_tq(Line, Qs0, St1), - {[F1|Qs1],St2}; - false -> - {F1,St1} = expr(F0, St0), - {Qs1,St2} = lc_tq(Line, Qs0, St1), - {[F1 | Qs1],St2} - end; + {F1,St1} = expr(F0, St0), + {Qs1,St2} = lc_tq(Line, Qs0, St1), + {[F1|Qs1],St2}; lc_tq(_Line, [], St0) -> {[],St0}. @@ -527,7 +496,7 @@ fun_tq(L, {function,M,F,A}, St) when is_atom(M), is_atom(F), is_integer(A) -> fun_tq(Lf, {function,_,_,_}=ExtFun, St) -> {{'fun',Lf,ExtFun},St}; fun_tq(Lf, {clauses,Cs0}, St0) -> - {Cs1,St1} = fun_clauses(Cs0, St0), + {Cs1,St1} = clauses(Cs0, St0), {Fname,St2} = new_fun_name(St1), %% Set dummy values for Index and Uniq -- the real values will %% be assigned by beam_asm. @@ -535,18 +504,10 @@ fun_tq(Lf, {clauses,Cs0}, St0) -> {{'fun',Lf,{clauses,Cs1},{Index,Uniq,Fname}},St2}. fun_tq(Line, Cs0, St0, Name) -> - {Cs1,St1} = fun_clauses(Cs0, St0), + {Cs1,St1} = clauses(Cs0, St0), {Fname,St2} = new_fun_name(St1, Name), {{named_fun,Line,Name,Cs1,{0,0,Fname}},St2}. -fun_clauses([{clause,L,H0,G0,B0}|Cs0], St0) -> - {H,St1} = head(H0, St0), - {G,St2} = guard(G0, St1), - {B,St3} = exprs(B0, St2), - {Cs,St4} = fun_clauses(Cs0, St3), - {[{clause,L,H,G,B}|Cs],St4}; -fun_clauses([], St) -> {[],St}. - %% new_fun_name(State) -> {FunName,State}. new_fun_name(St) -> @@ -571,7 +532,6 @@ pattern_element({bin_element,Line,Expr0,Size0,Type0}, {Es,St0}) -> {[{bin_element,Line,Expr,Size,Type}|Es],St2}. pat_bit_size(default, St) -> {default,St}; -pat_bit_size({atom,_La,all}=All, St) -> {All,St}; pat_bit_size({var,_Lv,_V}=Var, St) -> {Var,St}; pat_bit_size(Size, St) -> Line = element(2, Size), @@ -592,8 +552,7 @@ coerce_to_float({integer,L,I}=E, [float|_]) -> try {float,L,float(I)} catch - error:badarg -> E; - error:badarith -> E + error:badarg -> E end; coerce_to_float(E, _) -> E. @@ -647,25 +606,11 @@ string_to_conses(Line, Cs, Tail) -> %% import(Line, Imports, State) -> %% State' -%% imported(Name, Arity, State) -> -%% {yes,Module} | no -%% Handle import declarations and test for imported functions. No need to -%% check when building imports as code is correct. +%% Handle import declarations. -import({Mod,Fs}, St) -> +import({Mod,Fs}, #expand{ctype=Ctype0}=St) -> true = is_atom(Mod), - Mfs = from_list(Fs), - St#expand{imports=add_imports(Mod, Mfs, St#expand.imports)}. - -add_imports(Mod, [F|Fs], Is) -> - add_imports(Mod, Fs, orddict:store(F, Mod, Is)); -add_imports(_, [], Is) -> Is. - -imported(F, A, St) -> - case orddict:find({F,A}, St#expand.imports) of - {ok,Mod} -> {yes,Mod}; - error -> no - end. - -defined(F, A, St) -> - gb_sets:is_element({F,A}, St#expand.defined). + Ctype = foldl(fun(F, A) -> + A#{F=>{imported,Mod}} + end, Ctype0, Fs), + St#expand{ctype=Ctype}. diff --git a/lib/compiler/src/v3_codegen.erl b/lib/compiler/src/v3_codegen.erl index 2a89305f4d..6f1912c616 100644 --- a/lib/compiler/src/v3_codegen.erl +++ b/lib/compiler/src/v3_codegen.erl @@ -827,21 +827,24 @@ select_extract_bin([{var,Hd},{var,Tl}], Size0, Unit, Type, Flags, Vf, {bs_save2,CtxReg,{Ctx,Tl}}],Int1} end, {Es,clear_dead(Aft, I, Vdb),St}; -select_extract_bin([{var,Hd}], Size0, Unit, binary, Flags, Vf, +select_extract_bin([{var,Hd}], Size, Unit, binary, Flags, Vf, I, Vdb, Bef, Ctx, Body, St) -> - SizeReg = get_bin_size_reg(Size0, Bef), + %% Match the last segment of a binary. We KNOW that the size + %% must be 'all'. + Size = {atom,all}, %Assertion. {Es,Aft} = case vdb_find(Hd, Vdb) of {_,_,Lhd} when Lhd =< I -> + %% The result will not be used. Furthermore, since we + %% we are at the end of the binary, the position will + %% not be used again; thus, it is safe to do a cheaper + %% test of the unit. CtxReg = fetch_var(Ctx, Bef), - {case SizeReg =:= {atom,all} andalso is_context_unused(Body) of - true when Unit =:= 1 -> + {case Unit of + 1 -> []; - true -> - [{test,bs_test_unit,{f,Vf},[CtxReg,Unit]}]; - false -> - [{test,bs_skip_bits2,{f,Vf}, - [CtxReg,SizeReg,Unit,{field_flags,Flags}]}] + _ -> + [{test,bs_test_unit,{f,Vf},[CtxReg,Unit]}] end,Bef}; {_,_,_} -> case is_context_unused(Body) of @@ -853,7 +856,7 @@ select_extract_bin([{var,Hd}], Size0, Unit, binary, Flags, Vf, Name = bs_get_binary2, Live = max_reg(Bef#sr.reg), {[{test,Name,{f,Vf},Live, - [CtxReg,SizeReg,Unit,{field_flags,Flags}],Rhd}], + [CtxReg,Size,Unit,{field_flags,Flags}],Rhd}], Int1}; true -> %% Since the matching context will not be used again, @@ -868,7 +871,7 @@ select_extract_bin([{var,Hd}], Size0, Unit, binary, Flags, Vf, Name = bs_get_binary2, Live = max_reg(Int1#sr.reg), {[{test,Name,{f,Vf},Live, - [CtxReg,SizeReg,Unit,{field_flags,Flags}],CtxReg}], + [CtxReg,Size,Unit,{field_flags,Flags}],CtxReg}], Int1} end end, diff --git a/lib/compiler/src/v3_core.erl b/lib/compiler/src/v3_core.erl index 7d93e2ae16..830dd9973a 100644 --- a/lib/compiler/src/v3_core.erl +++ b/lib/compiler/src/v3_core.erl @@ -469,7 +469,8 @@ unforce_tree([#iset{var=#c_var{name=V},arg=Arg0}|Es], D0) -> unforce_tree(Es, D); unforce_tree([#icall{}=Call], D) -> unforce_tree_subst(Call, D); -unforce_tree([Top], _) -> Top. +unforce_tree([#c_var{name=V}], D) -> + gb_trees:get(V, D). unforce_tree_subst(#icall{module=#c_literal{val=erlang}, name=#c_literal{val='=:='}, @@ -1079,13 +1080,39 @@ bc_tq1(Line, E, [#igen{anno=GAnno,ceps=Ceps, bc_tq1(Line, E, [#ifilter{}=Filter|Qs], Mc, St) -> filter_tq(Line, E, Filter, Mc, St, Qs, fun bc_tq1/5); bc_tq1(_, {bin,Bl,Elements}, [], AccVar, St0) -> - {E,Pre,St} = expr({bin,Bl,[{bin_element,Bl, - {var,Bl,AccVar#c_var.name}, - {atom,Bl,all}, - [binary,{unit,1}]}|Elements]}, St0), + bc_tq_build(Bl, [], AccVar, Elements, St0); +bc_tq1(Line, E0, [], AccVar, St0) -> + BsFlags = [binary,{unit,1}], + BsSize = {atom,Line,all}, + {E1,Pre0,St1} = safe(E0, St0), + case E1 of + #c_var{name=VarName} -> + Var = {var,Line,VarName}, + Els = [{bin_element,Line,Var,BsSize,BsFlags}], + bc_tq_build(Line, Pre0, AccVar, Els, St1); + #c_literal{val=Val} when is_bitstring(Val) -> + Bits = bit_size(Val), + <<Int0:Bits>> = Val, + Int = {integer,Line,Int0}, + Sz = {integer,Line,Bits}, + Els = [{bin_element,Line,Int,Sz,[integer,{unit,1},big]}], + bc_tq_build(Line, Pre0, AccVar, Els, St1); + _ -> + %% Any other safe (cons, tuple, literal) is not a + %% bitstring. Force the evaluation to fail (and + %% generate a warning). + Els = [{bin_element,Line,{atom,Line,bad_value},BsSize,BsFlags}], + bc_tq_build(Line, Pre0, AccVar, Els, St1) + end. + +bc_tq_build(Line, Pre0, #c_var{name=AccVar}, Elements0, St0) -> + Elements = [{bin_element,Line,{var,Line,AccVar},{atom,Line,all}, + [binary,{unit,1}]}|Elements0], + {E,Pre,St} = expr({bin,Line,Elements}, St0), #a{anno=A} = Anno0 = get_anno(E), Anno = Anno0#a{anno=[compiler_generated,single_use|A]}, - {set_anno(E, Anno),Pre,St}. + {set_anno(E, Anno),Pre0++Pre,St}. + %% filter_tq(Line, Expr, Filter, Mc, State, [Qualifier], TqFun) -> %% {Case,[PreExpr],State}. @@ -1306,7 +1333,9 @@ bc_elem_size({bin,_,El}, St0) -> Vs = [V || {_,#c_var{name=V}} <- Vars0], {E,Pre,St} = bc_mul_pairs(F, #c_literal{val=Bits}, [], St0), {E,Pre,Vs,St} - end. + end; +bc_elem_size(_, _) -> + throw(impossible). bc_elem_size_1([{bin_element,_,_,{integer,_,N},Flags}|Es], Bits, Vars) -> {unit,U} = keyfind(unit, 1, Flags), @@ -1652,10 +1681,12 @@ pat_alias_map_pairs_1([]) -> []. pat_bin(Ps, St) -> [pat_segment(P, St) || P <- Ps]. -pat_segment({bin_element,_,Val,Size,[Type,{unit,Unit}|Flags]}, St) -> +pat_segment({bin_element,L,Val,Size,[Type,{unit,Unit}|Flags]}, St) -> + Anno = lineno_anno(L, St), {Pval,[],St1} = pattern(Val,St), {Psize,[],_St2} = pattern(Size,St1), - #c_bitstr{val=Pval,size=Psize, + #c_bitstr{anno=Anno, + val=Pval,size=Psize, unit=#c_literal{val=Unit}, type=#c_literal{val=Type}, flags=#c_literal{val=Flags}}. @@ -1852,27 +1883,22 @@ uguard(Pg, Gs0, Ks, St0) -> %% uexprs([Kexpr], [KnownVar], State) -> {[Kexpr],State}. uexprs([#imatch{anno=A,pat=P0,arg=Arg,fc=Fc}|Les], Ks, St0) -> - %% Optimise for simple set of unbound variable. - case upattern(P0, Ks, St0) of - {#c_var{},[],_Pvs,_Pus,_} -> - %% Throw our work away and just set to iset. + case upat_is_new_var(P0, Ks) of + true -> + %% Assignment to a new variable. uexprs([#iset{var=P0,arg=Arg}|Les], Ks, St0); - _Other -> - %% Throw our work away and set to icase. - if - Les =:= [] -> - %% Need to explicitly return match "value", make - %% safe for efficiency. - {La0,Lps,St1} = force_safe(Arg, St0), - La = mark_compiler_generated(La0), - Mc = #iclause{anno=A,pats=[P0],guard=[],body=[La]}, - uexprs(Lps ++ [#icase{anno=A, - args=[La0],clauses=[Mc],fc=Fc}], Ks, St1); - true -> - Mc = #iclause{anno=A,pats=[P0],guard=[],body=Les}, - uexprs([#icase{anno=A,args=[Arg], - clauses=[Mc],fc=Fc}], Ks, St0) - end + false when Les =:= [] -> + %% Need to explicitly return match "value", make + %% safe for efficiency. + {La0,Lps,St1} = force_safe(Arg, St0), + La = mark_compiler_generated(La0), + Mc = #iclause{anno=A,pats=[P0],guard=[],body=[La]}, + uexprs(Lps ++ [#icase{anno=A, + args=[La0],clauses=[Mc],fc=Fc}], Ks, St1); + false -> + Mc = #iclause{anno=A,pats=[P0],guard=[],body=Les}, + uexprs([#icase{anno=A,args=[Arg], + clauses=[Mc],fc=Fc}], Ks, St0) end; uexprs([Le0|Les0], Ks, St0) -> {Le1,St1} = uexpr(Le0, Ks, St0), @@ -1880,6 +1906,15 @@ uexprs([Le0|Les0], Ks, St0) -> {[Le1|Les1],St2}; uexprs([], _, St) -> {[],St}. +%% upat_is_new_var(Pattern, [KnownVar]) -> true|false. +%% Test whether the pattern is a single, previously unknown +%% variable. + +upat_is_new_var(#c_var{name=V}, Ks) -> + not is_element(V, Ks); +upat_is_new_var(_, _) -> + false. + %% Mark a "safe" as compiler-generated. mark_compiler_generated(#c_cons{anno=A,hd=H,tl=T}) -> ann_c_cons([compiler_generated|A], mark_compiler_generated(H), diff --git a/lib/compiler/src/v3_kernel.erl b/lib/compiler/src/v3_kernel.erl index 7ee564683b..4446d5ff1d 100644 --- a/lib/compiler/src/v3_kernel.erl +++ b/lib/compiler/src/v3_kernel.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1999-2013. All Rights Reserved. +%% Copyright Ericsson AB 1999-2015. All Rights Reserved. %% %% Licensed under the Apache License, Version 2.0 (the "License"); %% you may not use this file except in compliance with the License. @@ -117,7 +117,7 @@ copy_anno(Kdst, Ksrc) -> fcount=0, %Fun counter ds=cerl_sets:new() :: cerl_sets:set(), %Defined variables funs=[], %Fun functions - free=[], %Free variables + free=#{}, %Free variables ws=[] :: [warning()], %Warnings. guard_refc=0}). %> 0 means in guard @@ -143,8 +143,10 @@ attributes([]) -> []. include_attribute(type) -> false; include_attribute(spec) -> false; +include_attribute(callback) -> false; include_attribute(opaque) -> false; include_attribute(export_type) -> false; +include_attribute(record) -> false; include_attribute(_) -> true. function({#c_var{name={F,Arity}=FA},Body}, St0) -> @@ -1837,14 +1839,17 @@ handle_reuse_anno_1(V, _St) -> V. %% get_free(Name, Arity, State) -> [Free]. %% store_free(Name, Arity, [Free], State) -> State. -get_free(F, A, St) -> - case orddict:find({F,A}, St#kern.free) of - {ok,Val} -> Val; - error -> [] +get_free(F, A, #kern{free=FreeMap}) -> + Key = {F,A}, + case FreeMap of + #{Key:=Val} -> Val; + _ -> [] end. -store_free(F, A, Free, St) -> - St#kern{free=orddict:store({F,A}, Free, St#kern.free)}. +store_free(F, A, Free, #kern{free=FreeMap0}=St) -> + Key = {F,A}, + FreeMap = FreeMap0#{Key=>Free}, + St#kern{free=FreeMap}. break_rets({break,Rs}) -> Rs; break_rets(return) -> []. diff --git a/lib/compiler/test/Makefile b/lib/compiler/test/Makefile index 6553d10077..c2d757da4d 100644 --- a/lib/compiler/test/Makefile +++ b/lib/compiler/test/Makefile @@ -11,6 +11,8 @@ MODULES= \ beam_validator_SUITE \ beam_disasm_SUITE \ beam_except_SUITE \ + beam_reorder_SUITE \ + beam_type_SUITE \ beam_utils_SUITE \ bs_bincomp_SUITE \ bs_bit_binaries_SUITE \ @@ -43,6 +45,8 @@ NO_OPT= \ andor \ apply \ beam_except \ + beam_reorder \ + beam_type \ beam_utils \ bs_construct \ bs_match \ @@ -105,7 +109,7 @@ RELSYSDIR = $(RELEASE_PATH)/compiler_test # ---------------------------------------------------- ERL_MAKE_FLAGS += -ERL_COMPILE_FLAGS += -I$(ERL_TOP)/lib/test_server/include +clint +clint0 +ERL_COMPILE_FLAGS += +clint +clint0 EBIN = . diff --git a/lib/compiler/test/andor_SUITE.erl b/lib/compiler/test/andor_SUITE.erl index fae9597c8a..9736f75fe8 100644 --- a/lib/compiler/test/andor_SUITE.erl +++ b/lib/compiler/test/andor_SUITE.erl @@ -25,7 +25,7 @@ combined/1,in_case/1,before_and_inside_if/1, slow_compilation/1]). --include_lib("test_server/include/test_server.hrl"). +-include_lib("common_test/include/ct.hrl"). suite() -> [{ct_hooks,[ts_install_cth]}]. @@ -54,28 +54,28 @@ end_per_group(_GroupName, Config) -> t_case(Config) when is_list(Config) -> %% We test boolean cases almost but not quite like cases %% generated by andalso/orelse. - ?line less = t_case_a(1, 2), - ?line not_less = t_case_a(2, 2), - ?line {'EXIT',{{case_clause,false},_}} = (catch t_case_b({x,y,z}, 2)), - ?line {'EXIT',{{case_clause,true},_}} = (catch t_case_b(a, a)), - ?line eq = t_case_c(a, a), - ?line ne = t_case_c(42, []), - ?line t = t_case_d(x, x, true), - ?line f = t_case_d(x, x, false), - ?line f = t_case_d(x, y, true), - ?line {'EXIT',{badarg,_}} = (catch t_case_d(x, y, blurf)), - ?line true = (catch t_case_e({a,b}, {a,b})), - ?line false = (catch t_case_e({a,b}, 42)), - - ?line true = t_case_xy(42, 100, 700), - ?line true = t_case_xy(42, 100, whatever), - ?line false = t_case_xy(42, wrong, 700), - ?line false = t_case_xy(42, wrong, whatever), - - ?line true = t_case_xy(0, whatever, 700), - ?line true = t_case_xy(0, 100, 700), - ?line false = t_case_xy(0, whatever, wrong), - ?line false = t_case_xy(0, 100, wrong), + less = t_case_a(1, 2), + not_less = t_case_a(2, 2), + {'EXIT',{{case_clause,false},_}} = (catch t_case_b({x,y,z}, 2)), + {'EXIT',{{case_clause,true},_}} = (catch t_case_b(a, a)), + eq = t_case_c(a, a), + ne = t_case_c(42, []), + t = t_case_d(x, x, true), + f = t_case_d(x, x, false), + f = t_case_d(x, y, true), + {'EXIT',{badarg,_}} = (catch t_case_d(x, y, blurf)), + true = (catch t_case_e({a,b}, {a,b})), + false = (catch t_case_e({a,b}, 42)), + + true = t_case_xy(42, 100, 700), + true = t_case_xy(42, 100, whatever), + false = t_case_xy(42, wrong, 700), + false = t_case_xy(42, wrong, whatever), + + true = t_case_xy(0, whatever, 700), + true = t_case_xy(0, 100, 700), + false = t_case_xy(0, whatever, wrong), + false = t_case_xy(0, 100, wrong), ok. @@ -135,35 +135,35 @@ t_case_y(X, Y, Z) -> end). t_and_or(Config) when is_list(Config) -> - ?line true = true and true, - ?line false = true and false, - ?line false = false and true, - ?line false = false and false, - - ?line true = id(true) and true, - ?line false = id(true) and false, - ?line false = id(false) and true, - ?line false = id(false) and false, - - ?line true = true and id(true), - ?line false = true and id(false), - ?line false = false and id(true), - ?line false = false and id(false), - - ?line true = true or true, - ?line true = true or false, - ?line true = false or true, - ?line false = false or false, - - ?line true = id(true) or true, - ?line true = id(true) or false, - ?line true = id(false) or true, - ?line false = id(false) or false, - - ?line true = true or id(true), - ?line true = true or id(false), - ?line true = false or id(true), - ?line false = false or id(false), + true = true and true, + false = true and false, + false = false and true, + false = false and false, + + true = id(true) and true, + false = id(true) and false, + false = id(false) and true, + false = id(false) and false, + + true = true and id(true), + false = true and id(false), + false = false and id(true), + false = false and id(false), + + true = true or true, + true = true or false, + true = false or true, + false = false or false, + + true = id(true) or true, + true = id(true) or false, + true = id(false) or true, + false = id(false) or false, + + true = true or id(true), + true = true or id(false), + true = false or id(true), + false = false or id(false), True = id(true), @@ -187,28 +187,28 @@ t_andalso(Config) when is_list(Config) -> Ps = [{X,Y} || X <- Bs, Y <- Bs], lists:foreach(fun (P) -> t_andalso_1(P) end, Ps), - ?line true = true andalso true, - ?line false = true andalso false, - ?line false = false andalso true, - ?line false = false andalso false, + true = true andalso true, + false = true andalso false, + false = false andalso true, + false = false andalso false, - ?line true = ?GUARD(true andalso true), - ?line false = ?GUARD(true andalso false), - ?line false = ?GUARD(false andalso true), - ?line false = ?GUARD(false andalso false), + true = ?GUARD(true andalso true), + false = ?GUARD(true andalso false), + false = ?GUARD(false andalso true), + false = ?GUARD(false andalso false), - ?line false = false andalso glurf, - ?line false = false andalso exit(exit_now), + false = false andalso glurf, + false = false andalso exit(exit_now), - ?line true = not id(false) andalso not id(false), - ?line false = not id(false) andalso not id(true), - ?line false = not id(true) andalso not id(false), - ?line false = not id(true) andalso not id(true), + true = not id(false) andalso not id(false), + false = not id(false) andalso not id(true), + false = not id(true) andalso not id(false), + false = not id(true) andalso not id(true), - ?line {'EXIT',{badarg,_}} = (catch not id(glurf) andalso id(true)), - ?line {'EXIT',{badarg,_}} = (catch not id(false) andalso not id(glurf)), - ?line false = id(false) andalso not id(glurf), - ?line false = false andalso not id(glurf), + {'EXIT',{badarg,_}} = (catch not id(glurf) andalso id(true)), + {'EXIT',{badarg,_}} = (catch not id(false) andalso not id(glurf)), + false = id(false) andalso not id(glurf), + false = false andalso not id(glurf), true = begin (X1 = true) andalso X1, X1 end, false = false = begin (X2 = false) andalso X2, X2 end, @@ -220,28 +220,28 @@ t_orelse(Config) when is_list(Config) -> Ps = [{X,Y} || X <- Bs, Y <- Bs], lists:foreach(fun (P) -> t_orelse_1(P) end, Ps), - ?line true = true orelse true, - ?line true = true orelse false, - ?line true = false orelse true, - ?line false = false orelse false, + true = true orelse true, + true = true orelse false, + true = false orelse true, + false = false orelse false, - ?line true = ?GUARD(true orelse true), - ?line true = ?GUARD(true orelse false), - ?line true = ?GUARD(false orelse true), - ?line false = ?GUARD(false orelse false), + true = ?GUARD(true orelse true), + true = ?GUARD(true orelse false), + true = ?GUARD(false orelse true), + false = ?GUARD(false orelse false), - ?line true = true orelse glurf, - ?line true = true orelse exit(exit_now), + true = true orelse glurf, + true = true orelse exit(exit_now), - ?line true = not id(false) orelse not id(false), - ?line true = not id(false) orelse not id(true), - ?line true = not id(true) orelse not id(false), - ?line false = not id(true) orelse not id(true), + true = not id(false) orelse not id(false), + true = not id(false) orelse not id(true), + true = not id(true) orelse not id(false), + false = not id(true) orelse not id(true), - ?line {'EXIT',{badarg,_}} = (catch not id(glurf) orelse id(true)), - ?line {'EXIT',{badarg,_}} = (catch not id(true) orelse not id(glurf)), - ?line true = id(true) orelse not id(glurf), - ?line true = true orelse not id(glurf), + {'EXIT',{badarg,_}} = (catch not id(glurf) orelse id(true)), + {'EXIT',{badarg,_}} = (catch not id(true) orelse not id(glurf)), + true = id(true) orelse not id(glurf), + true = true orelse not id(glurf), true = begin (X1 = true) orelse X1, X1 end, false = begin (X2 = false) orelse X2, X2 end, @@ -255,7 +255,7 @@ t_andalso_1({X,Y}) -> X andalso Y -> true; true -> false end, - check(V1, X and Y). + V1 = id(X and Y). t_orelse_1({X,Y}) -> io:fwrite("~w orelse ~w: ",[X,Y]), @@ -264,19 +264,19 @@ t_orelse_1({X,Y}) -> X orelse Y -> true; true -> false end, - check(V1, X or Y). + V1 = id(X or Y). inside(Config) when is_list(Config) -> - ?line true = inside(-8, 1), - ?line false = inside(-53.5, -879798), - ?line false = inside(1.0, -879), - ?line false = inside(59, -879), - ?line false = inside(-11, 1.0), - ?line false = inside(100, 0.2), - ?line false = inside(100, 1.2), - ?line false = inside(-53.5, 4), - ?line false = inside(1.0, 5.3), - ?line false = inside(59, 879), + true = inside(-8, 1), + false = inside(-53.5, -879798), + false = inside(1.0, -879), + false = inside(59, -879), + false = inside(-11, 1.0), + false = inside(100, 0.2), + false = inside(100, 1.2), + false = inside(-53.5, 4), + false = inside(1.0, 5.3), + false = inside(59, 879), ok. inside(Xm, Ym) -> @@ -311,15 +311,15 @@ inside_guard(Xm, Ym, X, Y, W, H) -> {false,Xm,Ym,X,Y,W,H}. overlap(Config) when is_list(Config) -> - ?line true = overlap(7.0, 2.0, 8.0, 0.5), - ?line true = overlap(7.0, 2.0, 8.0, 2.5), - ?line true = overlap(7.0, 2.0, 5.3, 2), - ?line true = overlap(7.0, 2.0, 0.0, 100.0), - - ?line false = overlap(-1, 2, -35, 0.5), - ?line false = overlap(-1, 2, 777, 0.5), - ?line false = overlap(-1, 2, 2, 10), - ?line false = overlap(2, 10, 12, 55.3), + true = overlap(7.0, 2.0, 8.0, 0.5), + true = overlap(7.0, 2.0, 8.0, 2.5), + true = overlap(7.0, 2.0, 5.3, 2), + true = overlap(7.0, 2.0, 0.0, 100.0), + + false = overlap(-1, 2, -35, 0.5), + false = overlap(-1, 2, 777, 0.5), + false = overlap(-1, 2, 2, 10), + false = overlap(2, 10, 12, 55.3), ok. overlap(Pos1, Len1, Pos2, Len2) -> @@ -343,33 +343,33 @@ overlap(Pos1, Len1, Pos2, Len2) -> -define(COMB(A,B,C), (A andalso B orelse C)). combined(Config) when is_list(Config) -> - ?line false = comb(false, false, false), - ?line true = comb(false, false, true), - ?line false = comb(false, true, false), - ?line true = comb(false, true, true), - - ?line false = comb(true, false, false), - ?line true = comb(true, true, false), - ?line true = comb(true, false, true), - ?line true = comb(true, true, true), - - ?line false = comb(false, blurf, false), - ?line true = comb(false, blurf, true), - ?line true = comb(true, true, blurf), - - ?line false = ?COMB(false, false, false), - ?line true = ?COMB(false, false, true), - ?line false = ?COMB(false, true, false), - ?line true = ?COMB(false, true, true), - - ?line false = ?COMB(true, false, false), - ?line true = ?COMB(true, true, false), - ?line true = ?COMB(true, false, true), - ?line true = ?COMB(true, true, true), - - ?line false = ?COMB(false, blurf, false), - ?line true = ?COMB(false, blurf, true), - ?line true = ?COMB(true, true, blurf), + false = comb(false, false, false), + true = comb(false, false, true), + false = comb(false, true, false), + true = comb(false, true, true), + + false = comb(true, false, false), + true = comb(true, true, false), + true = comb(true, false, true), + true = comb(true, true, true), + + false = comb(false, blurf, false), + true = comb(false, blurf, true), + true = comb(true, true, blurf), + + false = ?COMB(false, false, false), + true = ?COMB(false, false, true), + false = ?COMB(false, true, false), + true = ?COMB(false, true, true), + + false = ?COMB(true, false, false), + true = ?COMB(true, true, false), + true = ?COMB(true, false, true), + true = ?COMB(true, true, true), + + false = ?COMB(false, blurf, false), + true = ?COMB(false, blurf, true), + true = ?COMB(true, true, blurf), false = simple_comb(false, false), false = simple_comb(false, true), @@ -412,13 +412,13 @@ simple_comb(A, B) -> %% Test that a boolean expression in a case expression is properly %% optimized (in particular, that the error behaviour is correct). in_case(Config) when is_list(Config) -> - ?line edge_rings = in_case_1(1, 1, 1, 1, 1), - ?line not_loop = in_case_1(0.5, 1, 1, 1, 1), - ?line loop = in_case_1(0.5, 0.9, 1.1, 1, 4), - ?line {'EXIT',{badarith,_}} = (catch in_case_1(1, 1, 1, 1, 0)), - ?line {'EXIT',{badarith,_}} = (catch in_case_1(1, 1, 1, 1, nan)), - ?line {'EXIT',{badarg,_}} = (catch in_case_1(1, 1, 1, blurf, 1)), - ?line {'EXIT',{badarith,_}} = (catch in_case_1([nan], 1, 1, 1, 1)), + edge_rings = in_case_1(1, 1, 1, 1, 1), + not_loop = in_case_1(0.5, 1, 1, 1, 1), + loop = in_case_1(0.5, 0.9, 1.1, 1, 4), + {'EXIT',{badarith,_}} = (catch in_case_1(1, 1, 1, 1, 0)), + {'EXIT',{badarith,_}} = (catch in_case_1(1, 1, 1, 1, nan)), + {'EXIT',{badarg,_}} = (catch in_case_1(1, 1, 1, blurf, 1)), + {'EXIT',{badarith,_}} = (catch in_case_1([nan], 1, 1, 1, 1)), ok. in_case_1(LenUp, LenDw, LenN, Rotation, Count) -> @@ -451,23 +451,23 @@ in_case_1_guard(LenUp, LenDw, LenN, Rotation, Count) -> end. before_and_inside_if(Config) when is_list(Config) -> - ?line no = before_and_inside_if([a], [b], delete), - ?line no = before_and_inside_if([a], [b], x), - ?line no = before_and_inside_if([a], [], delete), - ?line no = before_and_inside_if([a], [], x), - ?line no = before_and_inside_if([], [], delete), - ?line yes = before_and_inside_if([], [], x), - ?line yes = before_and_inside_if([], [b], delete), - ?line yes = before_and_inside_if([], [b], x), - - ?line {ch1,ch2} = before_and_inside_if_2([a], [b], blah), - ?line {ch1,ch2} = before_and_inside_if_2([a], [b], xx), - ?line {ch1,ch2} = before_and_inside_if_2([a], [], blah), - ?line {ch1,ch2} = before_and_inside_if_2([a], [], xx), - ?line {no,no} = before_and_inside_if_2([], [b], blah), - ?line {no,no} = before_and_inside_if_2([], [b], xx), - ?line {ch1,no} = before_and_inside_if_2([], [], blah), - ?line {no,ch2} = before_and_inside_if_2([], [], xx), + no = before_and_inside_if([a], [b], delete), + no = before_and_inside_if([a], [b], x), + no = before_and_inside_if([a], [], delete), + no = before_and_inside_if([a], [], x), + no = before_and_inside_if([], [], delete), + yes = before_and_inside_if([], [], x), + yes = before_and_inside_if([], [b], delete), + yes = before_and_inside_if([], [b], x), + + {ch1,ch2} = before_and_inside_if_2([a], [b], blah), + {ch1,ch2} = before_and_inside_if_2([a], [b], xx), + {ch1,ch2} = before_and_inside_if_2([a], [], blah), + {ch1,ch2} = before_and_inside_if_2([a], [], xx), + {no,no} = before_and_inside_if_2([], [b], blah), + {no,no} = before_and_inside_if_2([], [b], xx), + {ch1,no} = before_and_inside_if_2([], [], blah), + {no,ch2} = before_and_inside_if_2([], [], xx), ok. %% Thanks to Simon Cornish and Kostis Sagonas. @@ -539,14 +539,6 @@ slow_compilation_1(T, _) when element(1, T) == a -> %% Utilities. -check(V1, V0) -> - if V1 /= V0 -> - io:fwrite("error: ~w.\n", [V1]), - ?t:fail(); - true -> - io:fwrite("ok: ~w.\n", [V1]) - end. - echo(X) -> io:fwrite("eval(~w); ",[X]), X. diff --git a/lib/compiler/test/apply_SUITE.erl b/lib/compiler/test/apply_SUITE.erl index 3425553fed..8abcfe9dac 100644 --- a/lib/compiler/test/apply_SUITE.erl +++ b/lib/compiler/test/apply_SUITE.erl @@ -24,7 +24,7 @@ -export([foo/0,bar/1,baz/2]). --include_lib("test_server/include/test_server.hrl"). +-include_lib("common_test/include/ct.hrl"). suite() -> [{ct_hooks,[ts_install_cth]}]. @@ -53,44 +53,44 @@ end_per_group(_GroupName, Config) -> -define(APPLY2(M, F, A1, A2), (fun(Res) -> Res = M:F(A1, A2) end)(apply(M, F, [A1,A2]))). mfa(Config) when is_list(Config) -> - ?line ok = ?APPLY0(?MODULE, foo), - ?line {[a,b]} = ?APPLY1(?MODULE, bar, [a,b]), - ?line {39,{a}} = ?APPLY2(?MODULE, baz, 39, {a}), - - ?line Mod = id(?MODULE), - ?line ok = ?APPLY0(Mod, foo), - ?line {[a,b]} = ?APPLY1(Mod, bar, [a,b]), - ?line {39,{a}} = ?APPLY2(Mod, baz, 39, {a}), - - ?line ok = ?APPLY0(?MODULE, (id(foo))), - ?line {[a,b]} = ?APPLY1(?MODULE, (id(bar)), [a,b]), - ?line {39,{a}} = ?APPLY2(?MODULE, (id(baz)), 39, {a}), - - ?line ok = ?APPLY0(Mod, (id(foo))), - ?line {[a,b]} = ?APPLY1(Mod, (id(bar)), [a,b]), - ?line {39,{a}} = ?APPLY2(Mod, (id(baz)), 39, {a}), - - ?line {'EXIT',_} = (catch ?APPLY2(Mod, (id(bazzzzzz)), a, b)), - ?line {'EXIT',_} = (catch ?APPLY2({}, baz, a, b)), - ?line {'EXIT',_} = (catch ?APPLY2(?MODULE, [], a, b)), - - ?line ok = apply(Mod, foo, id([])), - ?line {[a,b|c]} = apply(Mod, bar, id([[a,b|c]])), - ?line {[xx],{a}} = apply(?MODULE, baz, id([[xx],{a}])), - - ?line Erlang = id(erlang), - ?line Self = self(), - ?line Self = ?APPLY0(Erlang, self), - ?line 42.0 = ?APPLY1(Erlang, abs, -42.0), - ?line b = ?APPLY2(Erlang, element, 2, {a,b,c}), - ?line true = ?APPLY1(Erlang, is_function, fun erlang:list_to_binary/1), - ?line true = ?APPLY1(Erlang, is_function, fun() -> ok end), - ?line false = ?APPLY1(Erlang, is_function, blurf), - ?line true = ?APPLY2(Erlang, is_function, fun erlang:list_to_binary/1, 1), - ?line true = ?APPLY2(Erlang, is_function, fun() -> ok end, 0), - ?line false = ?APPLY2(Erlang, is_function, blurf, 0), - - ?line apply(Mod, foo, []). + ok = ?APPLY0(?MODULE, foo), + {[a,b]} = ?APPLY1(?MODULE, bar, [a,b]), + {39,{a}} = ?APPLY2(?MODULE, baz, 39, {a}), + + Mod = id(?MODULE), + ok = ?APPLY0(Mod, foo), + {[a,b]} = ?APPLY1(Mod, bar, [a,b]), + {39,{a}} = ?APPLY2(Mod, baz, 39, {a}), + + ok = ?APPLY0(?MODULE, (id(foo))), + {[a,b]} = ?APPLY1(?MODULE, (id(bar)), [a,b]), + {39,{a}} = ?APPLY2(?MODULE, (id(baz)), 39, {a}), + + ok = ?APPLY0(Mod, (id(foo))), + {[a,b]} = ?APPLY1(Mod, (id(bar)), [a,b]), + {39,{a}} = ?APPLY2(Mod, (id(baz)), 39, {a}), + + {'EXIT',_} = (catch ?APPLY2(Mod, (id(bazzzzzz)), a, b)), + {'EXIT',_} = (catch ?APPLY2({}, baz, a, b)), + {'EXIT',_} = (catch ?APPLY2(?MODULE, [], a, b)), + + ok = apply(Mod, foo, id([])), + {[a,b|c]} = apply(Mod, bar, id([[a,b|c]])), + {[xx],{a}} = apply(?MODULE, baz, id([[xx],{a}])), + + Erlang = id(erlang), + Self = self(), + Self = ?APPLY0(Erlang, self), + 42.0 = ?APPLY1(Erlang, abs, -42.0), + b = ?APPLY2(Erlang, element, 2, {a,b,c}), + true = ?APPLY1(Erlang, is_function, fun erlang:list_to_binary/1), + true = ?APPLY1(Erlang, is_function, fun() -> ok end), + false = ?APPLY1(Erlang, is_function, blurf), + true = ?APPLY2(Erlang, is_function, fun erlang:list_to_binary/1, 1), + true = ?APPLY2(Erlang, is_function, fun() -> ok end, 0), + false = ?APPLY2(Erlang, is_function, blurf, 0), + + apply(Mod, foo, []). foo() -> ok. @@ -106,21 +106,21 @@ baz(A, B) -> -define(FUNAPPLY2(F, A1, A2), (fun(Res) -> Res = F(A1, A2) end)(apply(F, [A1,A2]))). fun_apply(Config) when is_list(Config) -> - ?line Self = self(), + Self = self(), - ?line Self = ?FUNAPPLY0(fun() -> self() end), - ?line Self = ?FUNAPPLY0((id(fun() -> self() end))), - ?line ok = ?FUNAPPLY0(fun ?MODULE:foo/0), - ?line ok = ?FUNAPPLY0((id(fun ?MODULE:foo/0))), + Self = ?FUNAPPLY0(fun() -> self() end), + Self = ?FUNAPPLY0((id(fun() -> self() end))), + ok = ?FUNAPPLY0(fun ?MODULE:foo/0), + ok = ?FUNAPPLY0((id(fun ?MODULE:foo/0))), - ?line -42 = ?FUNAPPLY1(fun(A) -> -A end, 42), - ?line [x,yy] = ?FUNAPPLY1((id(fun(T) -> [x|T] end)), [yy]), - ?line {[a|b]} = ?FUNAPPLY1(fun ?MODULE:bar/1, [a|b]), - ?line {[a|b]} = ?FUNAPPLY1((id(fun ?MODULE:bar/1)), [a|b]), + -42 = ?FUNAPPLY1(fun(A) -> -A end, 42), + [x,yy] = ?FUNAPPLY1((id(fun(T) -> [x|T] end)), [yy]), + {[a|b]} = ?FUNAPPLY1(fun ?MODULE:bar/1, [a|b]), + {[a|b]} = ?FUNAPPLY1((id(fun ?MODULE:bar/1)), [a|b]), - ?line {a,b} = ?FUNAPPLY2(fun(A, B) -> {A,B} end, a, b), - ?line {a,[b]} = ?FUNAPPLY2((id(fun(A, B) -> {A,B} end)), a, [b]), - ?line {42,{a}} = ?FUNAPPLY2((id(fun ?MODULE:baz/2)), 42, {a}), + {a,b} = ?FUNAPPLY2(fun(A, B) -> {A,B} end, a, b), + {a,[b]} = ?FUNAPPLY2((id(fun(A, B) -> {A,B} end)), a, [b]), + {42,{a}} = ?FUNAPPLY2((id(fun ?MODULE:baz/2)), 42, {a}), ok. diff --git a/lib/compiler/test/beam_disasm_SUITE.erl b/lib/compiler/test/beam_disasm_SUITE.erl index 4dd92e7ed9..90598d9639 100644 --- a/lib/compiler/test/beam_disasm_SUITE.erl +++ b/lib/compiler/test/beam_disasm_SUITE.erl @@ -19,7 +19,7 @@ %% -module(beam_disasm_SUITE). --include_lib("test_server/include/test_server.hrl"). +-include_lib("common_test/include/ct.hrl"). -export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, init_per_group/2,end_per_group/2]). @@ -46,21 +46,20 @@ init_per_group(_GroupName, Config) -> end_per_group(_GroupName, Config) -> Config. -stripped(doc) -> - ["Check that stripped beam files can be disassembled"]; +%% Check that stripped beam files can be disassembled. stripped(Config) when is_list(Config) -> - ?line PrivDir = ?config(priv_dir, Config), - ?line SrcName = filename:join(PrivDir, "tmp.erl"), - ?line BeamName = filename:join(PrivDir, "tmp.beam"), + PrivDir = proplists:get_value(priv_dir, Config), + SrcName = filename:join(PrivDir, "tmp.erl"), + BeamName = filename:join(PrivDir, "tmp.beam"), Prog = <<"-module(tmp).\n-export([tmp/0]).\ntmp()->ok.\n">>, - ?line ok = file:write_file(SrcName, Prog), - ?line {ok, tmp} = + ok = file:write_file(SrcName, Prog), + {ok, tmp} = compile:file(SrcName, [{outdir, PrivDir}]), - ?line {beam_file, tmp, _, Attr, CompileInfo, [_|_]} = + {beam_file, tmp, _, Attr, CompileInfo, [_|_]} = beam_disasm:file(BeamName), - ?line true = is_list(Attr), - ?line true = is_list(CompileInfo), - ?line {ok, {tmp, _}} = beam_lib:strip(BeamName), - ?line {beam_file, tmp, _, [], [], [_|_]} = + true = is_list(Attr), + true = is_list(CompileInfo), + {ok, {tmp, _}} = beam_lib:strip(BeamName), + {beam_file, tmp, _, [], [], [_|_]} = beam_disasm:file(BeamName), ok. diff --git a/lib/compiler/test/beam_reorder_SUITE.erl b/lib/compiler/test/beam_reorder_SUITE.erl new file mode 100644 index 0000000000..4b2262f65b --- /dev/null +++ b/lib/compiler/test/beam_reorder_SUITE.erl @@ -0,0 +1,69 @@ +%% +%% %CopyrightBegin% +%% +%% Copyright Ericsson AB 2015. All Rights Reserved. +%% +%% Licensed under the Apache License, Version 2.0 (the "License"); +%% you may not use this file except in compliance with the License. +%% You may obtain a copy of the License at +%% +%% http://www.apache.org/licenses/LICENSE-2.0 +%% +%% Unless required by applicable law or agreed to in writing, software +%% distributed under the License is distributed on an "AS IS" BASIS, +%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied. +%% See the License for the specific language governing permissions and +%% limitations under the License. +%% +%% %CopyrightEnd% +%% +-module(beam_reorder_SUITE). + +-export([all/0,suite/0,groups/0,init_per_suite/1,end_per_suite/1, + init_per_group/2,end_per_group/2, + alloc/1]). + +suite() -> [{ct_hooks,[ts_install_cth]}]. + +all() -> + test_lib:recompile(?MODULE), + [{group,p}]. + +groups() -> + [{p,[parallel], + [alloc + ]}]. + +init_per_suite(Config) -> + Config. + +end_per_suite(_Config) -> + ok. + +init_per_group(_GroupName, Config) -> + Config. + +end_per_group(_GroupName, Config) -> + Config. + +-record(alloc, {version}). + +alloc(_Config) -> + {ok,42} = alloc_a(1, 2, #alloc{version=42}), + {a,b,c} = alloc_b(1, 2, #alloc{version={a,b,c}}), + ok. + +alloc_a(_U1, _U2, R) -> + V = R#alloc.version, + Res = id({ok,V}), + _ = id(0), + Res. + +alloc_b(_U1, _U2, R) -> + V = R#alloc.version, + Res = id(V), + _ = id(0), + Res. + +id(I) -> + I. diff --git a/lib/compiler/test/beam_type_SUITE.erl b/lib/compiler/test/beam_type_SUITE.erl new file mode 100644 index 0000000000..8d5c0190ed --- /dev/null +++ b/lib/compiler/test/beam_type_SUITE.erl @@ -0,0 +1,98 @@ +%% +%% %CopyrightBegin% +%% +%% Copyright Ericsson AB 2015. All Rights Reserved. +%% +%% Licensed under the Apache License, Version 2.0 (the "License"); +%% you may not use this file except in compliance with the License. +%% You may obtain a copy of the License at +%% +%% http://www.apache.org/licenses/LICENSE-2.0 +%% +%% Unless required by applicable law or agreed to in writing, software +%% distributed under the License is distributed on an "AS IS" BASIS, +%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied. +%% See the License for the specific language governing permissions and +%% limitations under the License. +%% +%% %CopyrightEnd% +%% +-module(beam_type_SUITE). + +-export([all/0,suite/0,groups/0,init_per_suite/1,end_per_suite/1, + init_per_group/2,end_per_group/2, + integers/1,coverage/1,booleans/1]). + +suite() -> [{ct_hooks,[ts_install_cth]}]. + +all() -> + test_lib:recompile(?MODULE), + [{group,p}]. + +groups() -> + [{p,[parallel], + [integers, + coverage, + booleans + ]}]. + +init_per_suite(Config) -> + Config. + +end_per_suite(_Config) -> + ok. + +init_per_group(_GroupName, Config) -> + Config. + +end_per_group(_GroupName, Config) -> + Config. + +integers(_Config) -> + a = do_integers_1(2#11000), + b = do_integers_1(2#11001), + + a = do_integers_2(<<0:1>>), + {'EXIT',{{case_clause,-1},_}} = (catch do_integers_2(<<1:1>>)), + + ok. + +do_integers_1(B0) -> + B = B0 band 1, + case B band 15 of + 0 -> a; + 1 -> b + end. + +do_integers_2(Bin) -> + <<B:1/signed>> = Bin, + case B of + 0 -> a; + 1 -> b + end. + +coverage(_Config) -> + {'EXIT',{badarith,_}} = (catch id(1) bsl 0.5), + {'EXIT',{badarith,_}} = (catch id(2.0) bsl 2), + {'EXIT',{badarith,_}} = (catch a + 0.5), + {'EXIT',{badarith,_}} = (catch 2.0 * b), + + {'EXIT',{badarith,_}} = (catch id(42.0) / (1 bsl 2000)), + + id(id(42) band 387439739874298734983787934283479243879), + id(-1 band id(13)), + + ok. + +booleans(_Config) -> + {'EXIT',{{case_clause,_},_}} = (catch do_booleans(42)), + ok. + +do_booleans(B) -> + case is_integer(B) of + yes -> yes; + no -> no + end. + +id(I) -> + I. diff --git a/lib/compiler/test/beam_validator_SUITE.erl b/lib/compiler/test/beam_validator_SUITE.erl index 69391b15eb..d27512b6eb 100644 --- a/lib/compiler/test/beam_validator_SUITE.erl +++ b/lib/compiler/test/beam_validator_SUITE.erl @@ -34,18 +34,17 @@ undef_label/1,illegal_instruction/1,failing_gc_guard_bif/1, map_field_lists/1]). --include_lib("test_server/include/test_server.hrl"). +-include_lib("common_test/include/ct.hrl"). init_per_testcase(Case, Config) when is_atom(Case), is_list(Config) -> - Dog = test_server:timetrap(?t:minutes(10)), - [{watchdog,Dog}|Config]. + Config. end_per_testcase(Case, Config) when is_atom(Case), is_list(Config) -> - Dog = ?config(watchdog, Config), - ?t:timetrap_cancel(Dog), ok. -suite() -> [{ct_hooks,[ts_install_cth]}]. +suite() -> + [{ct_hooks,[ts_install_cth]}, + {timetrap,{minutes,10}}]. all() -> test_lib:recompile(?MODULE), @@ -78,7 +77,7 @@ end_per_group(_GroupName, Config) -> compiler_bug(Config) when is_list(Config) -> %% Check that the compiler returns an error if we try to %% assemble one of the bad '.S' files. - Data = ?config(data_dir, Config), + Data = proplists:get_value(data_dir, Config), File = filename:join(Data, "compiler_bug"), error = compile:file(File, [from_asm,report_errors,time]), @@ -93,43 +92,41 @@ compiler_bug(Config) when is_list(Config) -> %% The following code is stupid but it should compile. stupid_but_valid(Config) when is_list(Config) -> AnAtom = nisse, - ?line try setelement(5, setelement(6, AnAtom, value), another_value) of - Term -> ?line ?t:fail({what_happened,Term}) - catch - error:badarg -> ok - end, + try setelement(5, setelement(6, AnAtom, value), another_value) of + Term -> ct:fail({what_happened,Term}) + catch + error:badarg -> ok + end, ok. xrange(Config) when is_list(Config) -> Errors = do_val(xrange, Config), - ?line - [{{t,sum_1,2}, - {{bif,'+',{f,0},[{x,-1},{x,1}],{x,0}},4, - {uninitialized_reg,{x,-1}}}}, - {{t,sum_2,2}, - {{bif,'+',{f,0},[{x,0},{x,1024}],{x,0}},4, - {uninitialized_reg,{x,1024}}}}, - {{t,sum_3,2}, - {{bif,'+',{f,0},[{x,0},{x,1}],{x,-1}},4, - {invalid_store,{x,-1},number}}}, - {{t,sum_4,2}, - {{bif,'+',{f,0},[{x,0},{x,1}],{x,1024}},4,limit}}] = Errors, + [{{t,sum_1,2}, + {{bif,'+',{f,0},[{x,-1},{x,1}],{x,0}},4, + {uninitialized_reg,{x,-1}}}}, + {{t,sum_2,2}, + {{bif,'+',{f,0},[{x,0},{x,1023}],{x,0}},4, + {uninitialized_reg,{x,1023}}}}, + {{t,sum_3,2}, + {{bif,'+',{f,0},[{x,0},{x,1}],{x,-1}},4, + {invalid_store,{x,-1},number}}}, + {{t,sum_4,2}, + {{bif,'+',{f,0},[{x,0},{x,1}],{x,1023}},4,limit}}] = Errors, ok. yrange(Config) when is_list(Config) -> Errors = do_val(yrange, Config), - ?line - [{{t,sum_1,2}, - {{move,{x,1},{y,-1}},5, - {invalid_store,{y,-1},term}}}, - {{t,sum_2,2}, - {{bif,'+',{f,0},[{x,0},{y,1024}],{x,0}},7, - {uninitialized_reg,{y,1024}}}}, - {{t,sum_3,2}, - {{move,{x,1},{y,1024}},5,limit}}, - {{t,sum_4,2}, - {{move,{x,1},{y,-1}},5, - {invalid_store,{y,-1},term}}}] = Errors, + [{{t,sum_1,2}, + {{move,{x,1},{y,-1}},5, + {invalid_store,{y,-1},term}}}, + {{t,sum_2,2}, + {{bif,'+',{f,0},[{x,0},{y,1024}],{x,0}},7, + {uninitialized_reg,{y,1024}}}}, + {{t,sum_3,2}, + {{move,{x,1},{y,1024}},5,limit}}, + {{t,sum_4,2}, + {{move,{x,1},{y,-1}},5, + {invalid_store,{y,-1},term}}}] = Errors, ok. stack(Config) when is_list(Config) -> @@ -163,25 +160,23 @@ merge_undefined(Config) when is_list(Config) -> uninit(Config) when is_list(Config) -> Errors = do_val(uninit, Config), - ?line - [{{t,sum_1,2}, - {{move,{y,0},{x,0}},5,{uninitialized_reg,{y,0}}}}, - {{t,sum_2,2}, - {{call,1,{f,8}},5,{uninitialized_reg,{y,0}}}}, - {{t,sum_3,2}, - {{bif,'+',{f,0},[{x,0},{y,0}],{x,0}}, - 6, - {unassigned,{y,0}}}}] = Errors, + [{{t,sum_1,2}, + {{move,{y,0},{x,0}},5,{uninitialized_reg,{y,0}}}}, + {{t,sum_2,2}, + {{call,1,{f,8}},5,{uninitialized_reg,{y,0}}}}, + {{t,sum_3,2}, + {{bif,'+',{f,0},[{x,0},{y,0}],{x,0}}, + 6, + {unassigned,{y,0}}}}] = Errors, ok. unsafe_catch(Config) when is_list(Config) -> Errors = do_val(unsafe_catch, Config), - ?line - [{{t,small,2}, - {{bs_put_integer,{f,0},{integer,16},1, - {field_flags,[unsigned,big]},{y,0}}, - 20, - {unassigned,{y,0}}}}] = Errors, + [{{t,small,2}, + {{bs_put_integer,{f,0},{integer,16},1, + {field_flags,[unsigned,big]},{y,0}}, + 20, + {unassigned,{y,0}}}}] = Errors, ok. dead_code(Config) when is_list(Config) -> @@ -190,16 +185,14 @@ dead_code(Config) when is_list(Config) -> overwrite_catchtag(Config) when is_list(Config) -> Errors = do_val(overwrite_catchtag, Config), - ?line - [{{overwrite_catchtag,foo,1}, - {{move,{x,0},{y,0}},6,{catchtag,_}}}] = Errors, + [{{overwrite_catchtag,foo,1}, + {{move,{x,0},{y,0}},6,{catchtag,_}}}] = Errors, ok. overwrite_trytag(Config) when is_list(Config) -> Errors = do_val(overwrite_trytag, Config), - ?line - [{{overwrite_trytag,foo,1}, - {{kill,{y,2}},8,{trytag,_}}}] = Errors, + [{{overwrite_trytag,foo,1}, + {{kill,{y,2}},8,{trytag,_}}}] = Errors, ok. accessing_tags(Config) when is_list(Config) -> @@ -231,82 +224,77 @@ bad_catch_try(Config) when is_list(Config) -> cons_guard(Config) when is_list(Config) -> Errors = do_val(cons, Config), - ?line - [{{cons,foo,1}, - {{get_list,{x,0},{x,1},{x,2}}, - 5, - {bad_type,{needed,cons},{actual,term}}}}] = Errors, + [{{cons,foo,1}, + {{get_list,{x,0},{x,1},{x,2}}, + 5, + {bad_type,{needed,cons},{actual,term}}}}] = Errors, ok. freg_range(Config) when is_list(Config) -> Errors = do_val(freg_range, Config), - ?line - [{{t,sum_1,2}, - {{bif,fadd,{f,0},[{fr,-1},{fr,1}],{fr,0}}, - 5, - {bad_source,{fr,-1}}}}, - {{t,sum_2,2}, - {{bif,fadd,{f,0},[{fr,0},{fr,1024}],{fr,0}}, - 6, - {uninitialized_reg,{fr,1024}}}}, - {{t,sum_3,2}, - {{bif,fadd,{f,0},[{fr,0},{fr,1}],{fr,-1}}, - 7, - {bad_target,{fr,-1}}}}, - {{t,sum_4,2}, - {{bif,fadd,{f,0},[{fr,0},{fr,1}],{fr,1024}}, - 7, - limit}}] = Errors, + [{{t,sum_1,2}, + {{bif,fadd,{f,0},[{fr,-1},{fr,1}],{fr,0}}, + 5, + {bad_source,{fr,-1}}}}, + {{t,sum_2,2}, + {{bif,fadd,{f,0},[{fr,0},{fr,1024}],{fr,0}}, + 6, + {uninitialized_reg,{fr,1024}}}}, + {{t,sum_3,2}, + {{bif,fadd,{f,0},[{fr,0},{fr,1}],{fr,-1}}, + 7, + {bad_target,{fr,-1}}}}, + {{t,sum_4,2}, + {{bif,fadd,{f,0},[{fr,0},{fr,1}],{fr,1024}}, + 7, + limit}}] = Errors, ok. freg_uninit(Config) when is_list(Config) -> Errors = do_val(freg_uninit, Config), - ?line - [{{t,sum_1,2}, - {{bif,fadd,{f,0},[{fr,0},{fr,1}],{fr,0}}, - 6, - {uninitialized_reg,{fr,1}}}}, - {{t,sum_2,2}, - {{bif,fadd,{f,0},[{fr,0},{fr,1}],{fr,0}}, - 9, - {uninitialized_reg,{fr,0}}}}] = Errors, + [{{t,sum_1,2}, + {{bif,fadd,{f,0},[{fr,0},{fr,1}],{fr,0}}, + 6, + {uninitialized_reg,{fr,1}}}}, + {{t,sum_2,2}, + {{bif,fadd,{f,0},[{fr,0},{fr,1}],{fr,0}}, + 9, + {uninitialized_reg,{fr,0}}}}] = Errors, ok. freg_state(Config) when is_list(Config) -> Errors = do_val(freg_state, Config), - ?line - [{{t,sum_1,2}, - {{bif,fmul,{f,0},[{fr,0},{fr,1}],{fr,0}}, - 6, - {bad_floating_point_state,undefined}}}, - {{t,sum_2,2}, - {{fmove,{fr,0},{x,0}}, - 8, - {bad_floating_point_state,cleared}}}, - {{t,sum_3,2}, - {{bif,'-',{f,0},[{x,1},{x,0}],{x,1}}, - 8, - {unsafe_instruction,{float_error_state,cleared}}}}, - {{t,sum_4,2}, - {{fcheckerror,{f,0}}, - 4, - {bad_floating_point_state,undefined}}}, - {{t,sum_5,2}, - {fclearerror,5,{bad_floating_point_state,cleared}}}] = Errors, + [{{t,sum_1,2}, + {{bif,fmul,{f,0},[{fr,0},{fr,1}],{fr,0}}, + 6, + {bad_floating_point_state,undefined}}}, + {{t,sum_2,2}, + {{fmove,{fr,0},{x,0}}, + 8, + {bad_floating_point_state,cleared}}}, + {{t,sum_3,2}, + {{bif,'-',{f,0},[{x,1},{x,0}],{x,1}}, + 8, + {unsafe_instruction,{float_error_state,cleared}}}}, + {{t,sum_4,2}, + {{fcheckerror,{f,0}}, + 4, + {bad_floating_point_state,undefined}}}, + {{t,sum_5,2}, + {fclearerror,5,{bad_floating_point_state,cleared}}}] = Errors, ok. bad_bin_match(Config) when is_list(Config) -> - [{{t,t,1},{return,5,{match_context,{x,0}}}}] = - do_val(bad_bin_match, Config), - ok. + [{{t,t,1},{return,5,{match_context,{x,0}}}}] = + do_val(bad_bin_match, Config), + ok. bad_dsetel(Config) when is_list(Config) -> Errors = do_val(bad_dsetel, Config), - ?line - [{{t,t,1}, - {{set_tuple_element,{x,1},{x,0},1}, - 17, - illegal_context_for_set_tuple_element}}] = Errors, + [{{t,t,1}, + {{set_tuple_element,{x,1},{x,0},1}, + 17, + illegal_context_for_set_tuple_element}}] = Errors, ok. state_after_fault_in_catch(Config) when is_list(Config) -> @@ -382,9 +370,9 @@ illegal_instruction(Config) when is_list(Config) -> %% (Thanks to Kiran Khaladkar.) %% failing_gc_guard_bif(Config) when is_list(Config) -> - ?line ok = process_request(lists:seq(1, 36)), - ?line error = process_request([]), - ?line error = process_request(not_a_list), + ok = process_request(lists:seq(1, 36)), + error = process_request([]), + error = process_request(not_a_list), ok. process_request(ConfId) -> @@ -421,7 +409,7 @@ map_field_lists(Config) -> %%%------------------------------------------------------------------------- do_val(Mod, Config) -> - Data = ?config(data_dir, Config), + Data = proplists:get_value(data_dir, Config), Base = atom_to_list(Mod), File = filename:join(Data, Base), case compile:file(File, [from_asm,no_postopt,return_errors]) of diff --git a/lib/compiler/test/beam_validator_SUITE_data/xrange.S b/lib/compiler/test/beam_validator_SUITE_data/xrange.S index c6f20288f7..a76408dde3 100644 --- a/lib/compiler/test/beam_validator_SUITE_data/xrange.S +++ b/lib/compiler/test/beam_validator_SUITE_data/xrange.S @@ -20,7 +20,7 @@ {label,3}. {func_info,{atom,t},{atom,sum_2},2}. {label,4}. - {bif,'+',{f,0},[{x,0},{x,1024}],{x,0}}. + {bif,'+',{f,0},[{x,0},{x,1023}],{x,0}}. {'%live',1}. return. @@ -38,7 +38,7 @@ {label,7}. {func_info,{atom,t},{atom,sum_4},2}. {label,8}. - {bif,'+',{f,0},[{x,0},{x,1}],{x,1024}}. + {bif,'+',{f,0},[{x,0},{x,1}],{x,1023}}. {'%live',1}. return. diff --git a/lib/compiler/test/bs_bincomp_SUITE.erl b/lib/compiler/test/bs_bincomp_SUITE.erl index 1bf4e9d4a7..5e5f6e2169 100644 --- a/lib/compiler/test/bs_bincomp_SUITE.erl +++ b/lib/compiler/test/bs_bincomp_SUITE.erl @@ -26,9 +26,9 @@ init_per_group/2,end_per_group/2, byte_aligned/1,bit_aligned/1,extended_byte_aligned/1, extended_bit_aligned/1,mixed/1,filters/1,trim_coverage/1, - nomatch/1,sizes/1]). + nomatch/1,sizes/1,general_expressions/1]). --include_lib("test_server/include/test_server.hrl"). +-include_lib("common_test/include/ct.hrl"). suite() -> [{ct_hooks,[ts_install_cth]}]. @@ -36,7 +36,7 @@ all() -> test_lib:recompile(?MODULE), [byte_aligned, bit_aligned, extended_byte_aligned, extended_bit_aligned, mixed, filters, trim_coverage, - nomatch, sizes]. + nomatch, sizes, general_expressions]. groups() -> []. @@ -55,110 +55,114 @@ end_per_group(_GroupName, Config) -> byte_aligned(Config) when is_list(Config) -> cs_init(), - ?line <<"abcdefg">> = cs(<< <<(X+32)>> || <<X>> <= <<"ABCDEFG">> >>), + <<"abcdefg">> = cs(<< <<(X+32)>> || <<X>> <= <<"ABCDEFG">> >>), <<1:32/little,2:32/little,3:32/little,4:32/little>> = cs(<< <<X:32/little>> || <<X:32>> <= <<1:32,2:32,3:32,4:32>> >>), - ?line cs(<<1:32/little,2:32/little,3:32/little,4:32/little>> = - << <<X:32/little>> || <<X:16>> <= <<1:16,2:16,3:16,4:16>> >>), + cs(<<1:32/little,2:32/little,3:32/little,4:32/little>> = + << <<X:32/little>> || <<X:16>> <= <<1:16,2:16,3:16,4:16>> >>), cs_end(). bit_aligned(Config) when is_list(Config) -> cs_init(), - ?line <<$a:7,$b:7,$c:7,$d:7,$e:7,$f:7,$g:7>> = + <<$a:7,$b:7,$c:7,$d:7,$e:7,$f:7,$g:7>> = cs(<< <<(X+32):7>> || <<X>> <= <<"ABCDEFG">> >>), - ?line <<"ABCDEFG">> = + <<"ABCDEFG">> = cs(<< <<(X-32)>> || <<X:7>> <= <<$a:7,$b:7,$c:7,$d:7,$e:7,$f:7,$g:7>> >>), - ?line <<1:31/little,2:31/little,3:31/little,4:31/little>> = + <<1:31/little,2:31/little,3:31/little,4:31/little>> = cs(<< <<X:31/little>> || <<X:31>> <= <<1:31,2:31,3:31,4:31>> >>), - ?line <<1:31/little,2:31/little,3:31/little,4:31/little>> = + <<1:31/little,2:31/little,3:31/little,4:31/little>> = cs(<< <<X:31/little>> || <<X:15>> <= <<1:15,2:15,3:15,4:15>> >>), cs_end(). extended_byte_aligned(Config) when is_list(Config) -> cs_init(), - ?line <<"abcdefg">> = cs(<< <<(X+32)>> || X <- "ABCDEFG" >>), - ?line "abcdefg" = [(X+32) || <<X>> <= <<"ABCDEFG">>], - ?line <<1:32/little,2:32/little,3:32/little,4:32/little>> = + <<"abcdefg">> = cs(<< <<(X+32)>> || X <- "ABCDEFG" >>), + "abcdefg" = [(X+32) || <<X>> <= <<"ABCDEFG">>], + <<1:32/little,2:32/little,3:32/little,4:32/little>> = cs(<< <<X:32/little>> || X <- [1,2,3,4] >>), - ?line [256,512,768,1024] = + [256,512,768,1024] = [X || <<X:16/little>> <= <<1:16,2:16,3:16,4:16>>], cs_end(). extended_bit_aligned(Config) when is_list(Config) -> cs_init(), - ?line <<$a:7,$b:7,$c:7,$d:7,$e:7,$f:7,$g:7>> = + <<$a:7,$b:7,$c:7,$d:7,$e:7,$f:7,$g:7>> = cs(<< <<(X+32):7>> || X <- "ABCDEFG" >>), - ?line "ABCDEFG" = [(X-32) || <<X:7>> <= <<$a:7,$b:7,$c:7,$d:7,$e:7,$f:7,$g:7>>], - ?line <<1:31/little,2:31/little,3:31/little,4:31/little>> = + "ABCDEFG" = [(X-32) || <<X:7>> <= <<$a:7,$b:7,$c:7,$d:7,$e:7,$f:7,$g:7>>], + <<1:31/little,2:31/little,3:31/little,4:31/little>> = cs(<< <<X:31/little>> || X <- [1,2,3,4] >>), - ?line [256,512,768,1024] = + [256,512,768,1024] = [X || <<X:15/little>> <= <<1:15,2:15,3:15,4:15>>], cs_end(). mixed(Config) when is_list(Config) -> cs_init(), - ?line <<2,3,3,4,4,5,5,6>> = + <<2,3,3,4,4,5,5,6>> = cs(<< <<(X+Y)>> || <<X>> <= <<1,2,3,4>>, <<Y>> <= <<1,2>> >>), - ?line <<2,3,3,4,4,5,5,6>> = + <<2,3,3,4,4,5,5,6>> = << <<(X+Y)>> || <<X>> <= <<1,2,3,4>>, Y <- [1,2] >>, - ?line <<2,3,3,4,4,5,5,6>> = + <<2,3,3,4,4,5,5,6>> = cs(<< <<(X+Y)>> || X <- [1,2,3,4], Y <- [1,2] >>), One = id([1,2,3,4]), Two = id([1,2]), - ?line <<2,3,3,4,4,5,5,6>> = + <<2,3,3,4,4,5,5,6>> = cs(<< <<(X+Y)>> || X <- One, Y <- Two >>), - ?line [2,3,3,4,4,5,5,6] = + [2,3,3,4,4,5,5,6] = [(X+Y) || <<X>> <= <<1,2,3,4>>, <<Y>> <= <<1,2>>], - ?line [2,3,3,4,4,5,5,6] = + [2,3,3,4,4,5,5,6] = [(X+Y) || <<X>> <= <<1,2,3,4>>, Y <- [1,2]], - ?line <<2:3,3:3,3:3,4:3,4:3,5:3,5:3,6:3>> = + <<2:3,3:3,3:3,4:3,4:3,5:3,5:3,6:3>> = cs(<< <<(X+Y):3>> || <<X:3>> <= <<1:3,2:3,3:3,4:3>>, <<Y:3>> <= <<1:3,2:3>> >>), - ?line <<2:3,3:3,3:3,4:3,4:3,5:3,5:3,6:3>> = + <<2:3,3:3,3:3,4:3,4:3,5:3,5:3,6:3>> = cs(<< <<(X+Y):3>> || <<X:3>> <= <<1:3,2:3,3:3,4:3>>, Y <- [1,2] >>), - ?line <<2:3,3:3,3:3,4:3,4:3,5:3,5:3,6:3>> = + <<2:3,3:3,3:3,4:3,4:3,5:3,5:3,6:3>> = cs(<< <<(X+Y):3>> || X <- [1,2,3,4], Y <- [1,2] >>), - ?line <<2:3,3:3,3:3,4:3,4:3,5:3,5:3,6:3>> = + <<2:3,3:3,3:3,4:3,4:3,5:3,5:3,6:3>> = cs_default(<< <<(X+Y):3>> || {X,Y} <- [{1,1},{1,2},{2,1},{2,2}, {3,1},{3,2},{4,1},{4,2}] >>), - ?line [2,3,3,4,4,5,5,6] = + [2,3,3,4,4,5,5,6] = [(X+Y) || <<X:3>> <= <<1:3,2:3,3:3,4:3>>, <<Y:3>> <= <<1:3,2:3>>], - ?line [2,3,3,4,4,5,5,6] = + [2,3,3,4,4,5,5,6] = [(X+Y) || <<X:3>> <= <<1:3,2:3,3:3,4:3>>, {_,Y} <- [{a,1},{b,2}]], cs_end(). filters(Config) when is_list(Config) -> cs_init(), - ?line <<"BDF">> = - cs_default(<< <<(X-32)>> || <<X:7>> <= <<$a:7,$b:7,$c:7,$d:7,$e:7,$f:7,$g:7>>, - X rem 2 == 0>>), - ?line <<"abc">> = cs_default(<< <<(X+32)>> || X <- "ABCDEFG", - is_less_than(X, $D)>>), - ?line <<"efg">> = cs_default(<< <<(X+32)>> || X <- "ABCDEFG", - not is_less_than(X, $E)>>), - ?line <<"b">> = cs_default(<< <<(X+32)>> || X <- "ABCDEFG", - is_less_than(X, $D), - X rem 2 == 0>>), - ?line <<"eg">> = cs_default(<< <<(X+32)>> || X <- "ABCDEFG", - not is_less_than(X, $E), - X rem 2 == 1>>), + <<"BDF">> = + cs_default(<< <<(X-32)>> || + <<X:7>> <= <<$a:7,$b:7,$c:7,$d:7,$e:7,$f:7,$g:7>>, + X rem 2 == 0>>), + <<"abc">> = cs_default(<< <<(X+32)>> || + X <- "ABCDEFG", + is_less_than(X, $D)>>), + <<"efg">> = cs_default(<< <<(X+32)>> || + X <- "ABCDEFG", + not is_less_than(X, $E)>>), + <<"b">> = cs_default(<< <<(X+32)>> || + X <- "ABCDEFG", + is_less_than(X, $D), + X rem 2 == 0>>), + <<"eg">> = cs_default(<< <<(X+32)>> || + X <- "ABCDEFG", + not is_less_than(X, $E), + X rem 2 == 1>>), %% Filtering by a non-matching pattern. - ?line <<"abd">> = cs_default(<< <<X:8>> || - <<0:1,X:7>> <= <<$a:8,$b:8,1:1,$c:7,$d:8, - 1:1,$e:7,0:4>> >>), + <<"abd">> = cs_default(<< <<X:8>> || + <<0:1,X:7>> <= <<$a:8,$b:8,1:1,$c:7,$d:8, + 1:1,$e:7,0:4>> >>), - ?line <<42,42>> = cs_default(<< <<42:8>> || - 42 <- [1,2,3,42,43,42] >>), + <<42,42>> = cs_default(<< <<42:8>> || 42 <- [1,2,3,42,43,42] >>), cs_end(). is_less_than(X, C) when X < C -> true; is_less_than(_, _) -> false. trim_coverage(Config) when is_list(Config) -> - ?line <<0,0,0,2,0,0,5,48,0,11,219,174,0,0,0,0>> = coverage_materialiv(a, b, {1328,777134}), - ?line <<67,40,0,0,66,152,0,0,69,66,64,0>> = coverage_trimmer([42,19,777]), - ?line <<0,0,2,43,0,0,3,9,0,0,0,3,64,8,0,0,0,0,0,0, + <<0,0,0,2,0,0,5,48,0,11,219,174,0,0,0,0>> = coverage_materialiv(a, b, {1328,777134}), + <<67,40,0,0,66,152,0,0,69,66,64,0>> = coverage_trimmer([42,19,777]), + <<0,0,2,43,0,0,3,9,0,0,0,3,64,8,0,0,0,0,0,0, 64,68,0,0,0,0,0,0,192,171,198,0,0,0,0,0>> = coverage_lightfv(555, 777, {3.0,40.0,-3555.0}), ok. @@ -186,111 +190,153 @@ coverage_trimmer(Params) -> coverage_summer(A, B, C, D) -> A+B+C+D. nomatch(Config) when is_list(Config) -> - ?line <<>> = << <<X:8>> || X = {_,_} = [_|_] <- [1,2,3] >>, + <<>> = << <<X:8>> || X = {_,_} = [_|_] <- [1,2,3] >>, ok. sizes(Config) when is_list(Config) -> - ?line cs_init(), + cs_init(), Fun0 = fun(List) -> cs(<< <<E:8>> || E <- List >>) end, - ?line <<>> = Fun0([]), - ?line <<1>> = Fun0([1]), - ?line <<1,2>> = Fun0([1,2]), - ?line <<1,2,3>> = Fun0([1,2,3]), + <<>> = Fun0([]), + <<1>> = Fun0([1]), + <<1,2>> = Fun0([1,2]), + <<1,2,3>> = Fun0([1,2,3]), Fun1 = fun(List) -> cs(<< <<E:16>> || E <- List >>) end, - ?line <<>> = Fun1([]), - ?line <<1:16>> = Fun1([1]), - ?line <<1:16,2:16>> = Fun1([1,2]), - ?line <<1:16,2:16,3:16>> = Fun1([1,2,3]), + <<>> = Fun1([]), + <<1:16>> = Fun1([1]), + <<1:16,2:16>> = Fun1([1,2]), + <<1:16,2:16,3:16>> = Fun1([1,2,3]), Fun2 = fun(List) -> cs(<< <<E:4>> || E <- List >>) end, - ?line <<>> = Fun2([]), - ?line <<1:4>> = Fun2([1]), - ?line <<1:4,13:4>> = Fun2([1,13]), - ?line <<1:4,13:4,7:4>> = Fun2([1,13,7]), - ?line <<0:1000/unit:8>> = Fun2(lists:duplicate(2000, 0)), + <<>> = Fun2([]), + <<1:4>> = Fun2([1]), + <<1:4,13:4>> = Fun2([1,13]), + <<1:4,13:4,7:4>> = Fun2([1,13,7]), + <<0:1000/unit:8>> = Fun2(lists:duplicate(2000, 0)), Fun3 = fun(List) -> cs(<< <<E:3>> || E <- List >>) end, - ?line <<>> = Fun3([]), - ?line <<40,177,29:5>> = Fun3([1,2,1,3,0,7,5]), - ?line <<0:512/unit:3>> = Fun3(lists:duplicate(512, 0)), + <<>> = Fun3([]), + <<40,177,29:5>> = Fun3([1,2,1,3,0,7,5]), + <<0:512/unit:3>> = Fun3(lists:duplicate(512, 0)), Fun4 = fun(List, Size) -> cs(<< <<E:Size>> || E <- List >>) end, - ?line <<>> = Fun4([], 8), - ?line <<42:6>> = Fun4([42], 6), - ?line <<42:16>> = Fun4([42], 16), + <<>> = Fun4([], 8), + <<42:6>> = Fun4([42], 6), + <<42:16>> = Fun4([42], 16), Fun5 = fun(List, Sz1, Sz2, Sz3) -> cs(<< <<E:Sz1,(E+1):Sz2/unit:8,(E+2):Sz3/unit:8>> || E <- List >>) end, - ?line <<>> = Fun5([], 1, 1, 1), - ?line <<7:3,8:40,9:56>> = Fun5([7], 3, 5, 7), + <<>> = Fun5([], 1, 1, 1), + <<7:3,8:40,9:56>> = Fun5([7], 3, 5, 7), Fun6 = fun(List, Size) -> cs(<< <<E:8,(E+1):Size>> || E <- List >>) end, - ?line <<>> = Fun6([], 42), - ?line <<42,43:20>> = Fun6([42], 20), + <<>> = Fun6([], 42), + <<42,43:20>> = Fun6([42], 20), %% Binary generators. Fun10 = fun(Bin) -> cs(<< <<E:16>> || <<E:8>> <= Bin >>) end, - ?line <<>> = Fun10(<<>>), - ?line <<1:16>> = Fun10(<<1>>), - ?line <<1:16,2:16>> = Fun10(<<1,2>>), + <<>> = Fun10(<<>>), + <<1:16>> = Fun10(<<1>>), + <<1:16,2:16>> = Fun10(<<1,2>>), Fun11 = fun(Bin) -> cs(<< <<E:8>> || <<E:16>> <= Bin >>) end, - ?line <<>> = Fun11(<<>>), - ?line <<1>> = Fun11(<<1:16>>), - ?line <<1,2>> = Fun11(<<1:16,2:16>>), - ?line <<1,2>> = Fun11(<<1:16,2:16,0:1>>), - ?line <<1,2>> = Fun11(<<1:16,2:16,0:7>>), - ?line <<1,2>> = Fun11(<<1:16,2:16,42:8>>), - ?line <<1,2>> = Fun11(<<1:16,2:16,42:9>>), - ?line <<1,2>> = Fun11(<<1:16,2:16,255:15>>), + <<>> = Fun11(<<>>), + <<1>> = Fun11(<<1:16>>), + <<1,2>> = Fun11(<<1:16,2:16>>), + <<1,2>> = Fun11(<<1:16,2:16,0:1>>), + <<1,2>> = Fun11(<<1:16,2:16,0:7>>), + <<1,2>> = Fun11(<<1:16,2:16,42:8>>), + <<1,2>> = Fun11(<<1:16,2:16,42:9>>), + <<1,2>> = Fun11(<<1:16,2:16,255:15>>), Fun12 = fun(Bin, Sz1, Sz2) -> cs(<< <<E:Sz1>> || <<E:Sz2>> <= Bin >>) end, - ?line <<>> = Fun12(<<>>, 1, 1), - ?line Binary = list_to_binary(lists:seq(0, 255)), - ?line Binary = Fun12(Binary, 1, 1), - ?line Binary = Fun12(Binary, 4, 4), - ?line Binary = Fun12(Binary, 8, 8), - ?line <<17:9,19:9>> = Fun12(<<17:6,19:6>>, 9, 6), + <<>> = Fun12(<<>>, 1, 1), + Binary = list_to_binary(lists:seq(0, 255)), + Binary = Fun12(Binary, 1, 1), + Binary = Fun12(Binary, 4, 4), + Binary = Fun12(Binary, 8, 8), + <<17:9,19:9>> = Fun12(<<17:6,19:6>>, 9, 6), Fun13 = fun(Sz) -> cs_default(<< <<C:8>> || <<C:4>> <= <<1:4,2:4,3:4,0:Sz>> >>) end, - ?line <<1,2,3>> = Fun13(0), - ?line <<1,2,3,0>> = Fun13(4), - ?line <<1,2,3,0>> = Fun13(5), - ?line <<1,2,3,0>> = Fun13(6), - ?line <<1,2,3,0>> = Fun13(7), - ?line <<1,2,3,0,0>> = Fun13(8), + <<1,2,3>> = Fun13(0), + <<1,2,3,0>> = Fun13(4), + <<1,2,3,0>> = Fun13(5), + <<1,2,3,0>> = Fun13(6), + <<1,2,3,0>> = Fun13(7), + <<1,2,3,0,0>> = Fun13(8), <<0:3>> = cs_default(<< <<0:S>> || S <- [0,1,2] >>), <<0:3>> = cs_default(<< <<0:S>> || <<S>> <= <<0,1,2>> >>), - ?line {'EXIT',_} = (catch << <<C:4>> || <<C:8>> <= {1,2,3} >>), + {'EXIT',_} = (catch << <<C:4>> || <<C:8>> <= {1,2,3} >>), + + cs_end(), + ok. + +-define(BAD(E), {'EXIT',{badarg,_}} = (catch << (E) || _ <- [1,2,3] >>)). +-define(BAD_V(E), {'EXIT',{badarg,_}} = (catch << (E) || I <- [1,2,3] >>)). + +general_expressions(_) -> + <<1,2,3>> = << begin <<1,2,3>> end || _ <- [1] >>, + <<"abc">> = << begin <<"abc">> end || _ <- [1] >>, + <<1,2,3>> = << begin + I = <<(I0+1)>>, + id(I) + end || <<I0>> <= <<0,1,2>> >>, + <<1,2,3>> = << I || I <- [<<1,2>>,<<3>>] >>, + <<1,2,3>> = << (id(<<I>>)) || I <- [1,2,3] >>, + <<2,4>> = << case I rem 2 of + 0 -> <<I>>; + 1 -> <<>> + end || I <- [1,2,3,4,5] >>, + <<2,3,4,5,6,7>> = << << (id(<<J>>)) || J <- [2*I,2*I+1] >> || + I <- [1,2,3] >>, + <<1,2,2,3,4,4>> = << if + I rem 2 =:= 0 -> <<I,I>>; + true -> <<I>> + end || I <- [1,2,3,4] >>, + self() ! <<42>>, + <<42>> = << receive B -> B end || _ <- [1] >>, + <<10,5,3>> = << try + <<(10 div I)>> + catch _:_ -> + <<>> + end || I <- [0,1,2,3] >>, + + %% Failing expressions. + ?BAD(bad_atom), + ?BAD(42), + ?BAD(42.0), + ?BAD_V({ok,I}), + ?BAD_V([I]), + ?BAD_V(fun() -> I end), - ?line cs_end(), ok. +-undef(BAD). + cs_init() -> erts_debug:set_internal_state(available_internal_state, true), ok. diff --git a/lib/compiler/test/bs_bit_binaries_SUITE.erl b/lib/compiler/test/bs_bit_binaries_SUITE.erl index afee52c9b9..c1f8f12bf1 100644 --- a/lib/compiler/test/bs_bit_binaries_SUITE.erl +++ b/lib/compiler/test/bs_bit_binaries_SUITE.erl @@ -29,7 +29,7 @@ big_binary_to_and_from_list/1,send_and_receive/1, send_and_receive_alot/1]). --include_lib("test_server/include/test_server.hrl"). +-include_lib("common_test/include/ct.hrl"). suite() -> [{ct_hooks,[ts_install_cth]}]. @@ -59,9 +59,9 @@ end_per_group(_GroupName, Config) -> misc(Config) when is_list(Config) -> - ?line <<1:100>> = <<1:100>>, - ?line {ok,ok} = {match(7),match(9)}, - ?line {ok,ok} = {match1(15),match1(31)}, + <<1:100>> = <<1:100>>, + {ok,ok} = {match(7),match(9)}, + {ok,ok} = {match1(15),match1(31)}, ok. @@ -74,75 +74,75 @@ match1(N) -> ok. test_bit_size(Config) when is_list(Config) -> - ?line 101 = erlang:bit_size(<<1:101>>), - ?line 1001 = erlang:bit_size(<<1:1001>>), - ?line 1001 = erlang:bit_size(<<-10:1001>>), - ?line 80 = erlang:bit_size(<<1:80>>), - ?line 800 = erlang:bit_size(<<1:800>>), - ?line Bin = <<0:16#1000000>>, - ?line BigBin = list_to_bitstring([Bin||_ <- lists:seq(1,16#10)]++[<<1:1>>]), - ?line 16#10000001 = erlang:bit_size(BigBin), + 101 = erlang:bit_size(<<1:101>>), + 1001 = erlang:bit_size(<<1:1001>>), + 1001 = erlang:bit_size(<<-10:1001>>), + 80 = erlang:bit_size(<<1:80>>), + 800 = erlang:bit_size(<<1:800>>), + Bin = <<0:16#1000000>>, + BigBin = list_to_bitstring([Bin||_ <- lists:seq(1,16#10)]++[<<1:1>>]), + 16#10000001 = erlang:bit_size(BigBin), %% Only run these on computers with lots of memory %% HugeBin = list_to_bitstring([BigBin||_ <- lists:seq(1,16#10)]++[<<1:1>>]), %% 16#100000011 = erlang:bit_size(HugeBin), - ?line 0 = erlang:bit_size(<<>>), + 0 = erlang:bit_size(<<>>), ok. horrid_match(Config) when is_list(Config) -> - ?line <<1:4,B:24/bitstring>> = <<1:4,42:24/little>>, - ?line <<42:24/little>> = B, + <<1:4,B:24/bitstring>> = <<1:4,42:24/little>>, + <<42:24/little>> = B, ok. test_bitstr(Config) when is_list(Config) -> - ?line <<1:7,B/bitstring>> = <<1:7,<<1:1,6>>/bitstring>>, - ?line <<1:1,6>> = B, - ?line B = <<1:1,6>>, + <<1:7,B/bitstring>> = <<1:7,<<1:1,6>>/bitstring>>, + <<1:1,6>> = B, + B = <<1:1,6>>, ok. asymmetric_tests(Config) when is_list(Config) -> - ?line <<1:12>> = <<0,1:4>>, - ?line <<0,1:4>> = <<1:12>>, - ?line <<1:1,X/bitstring>> = <<128,255,0,0:2>>, - ?line <<1,254,0,0:1>> = X, - ?line X = <<1,254,0,0:1>>, - ?line <<1:1,X1:25/bitstring>> = <<128,255,0,0:2>>, - ?line <<1,254,0,0:1>> = X1, - ?line X1 = <<1,254,0,0:1>>, + <<1:12>> = <<0,1:4>>, + <<0,1:4>> = <<1:12>>, + <<1:1,X/bitstring>> = <<128,255,0,0:2>>, + <<1,254,0,0:1>> = X, + X = <<1,254,0,0:1>>, + <<1:1,X1:25/bitstring>> = <<128,255,0,0:2>>, + <<1,254,0,0:1>> = X1, + X1 = <<1,254,0,0:1>>, ok. big_asymmetric_tests(Config) when is_list(Config) -> - ?line <<1:875,1:12>> = <<1:875,0,1:4>>, - ?line <<1:875,0,1:4>> = <<1:875,1:12>>, - ?line <<1:1,X/bitstring>> = <<128,255,0,0:2,1:875>>, - ?line <<1,254,0,0:1,1:875>> = X, - ?line X = <<1,254,0,0:1,1:875>>, - ?line <<1:1,X1:900/bitstring>> = <<128,255,0,0:2,1:875>>, - ?line <<1,254,0,0:1,1:875>> = X1, - ?line X1 = <<1,254,0,0:1,1:875>>, + <<1:875,1:12>> = <<1:875,0,1:4>>, + <<1:875,0,1:4>> = <<1:875,1:12>>, + <<1:1,X/bitstring>> = <<128,255,0,0:2,1:875>>, + <<1,254,0,0:1,1:875>> = X, + X = <<1,254,0,0:1,1:875>>, + <<1:1,X1:900/bitstring>> = <<128,255,0,0:2,1:875>>, + <<1,254,0,0:1,1:875>> = X1, + X1 = <<1,254,0,0:1,1:875>>, ok. binary_to_and_from_list(Config) when is_list(Config) -> - ?line <<1,2,3,4,1:1>> = list_to_bitstring(bitstring_to_list(<<1,2,3,4,1:1>>)), - ?line [1,2,3,4,<<1:1>>] = bitstring_to_list(<<1,2,3,4,1:1>>), - ?line <<1:1,1,2,3,4>> = list_to_bitstring([<<1:1>>,1,2,3,4]), - ?line [128,129,1,130,<<0:1>>] = bitstring_to_list(<<1:1,1,2,3,4>>), + <<1,2,3,4,1:1>> = list_to_bitstring(bitstring_to_list(<<1,2,3,4,1:1>>)), + [1,2,3,4,<<1:1>>] = bitstring_to_list(<<1,2,3,4,1:1>>), + <<1:1,1,2,3,4>> = list_to_bitstring([<<1:1>>,1,2,3,4]), + [128,129,1,130,<<0:1>>] = bitstring_to_list(<<1:1,1,2,3,4>>), ok. big_binary_to_and_from_list(Config) when is_list(Config) -> - ?line <<1:800,2,3,4,1:1>> = + <<1:800,2,3,4,1:1>> = list_to_bitstring(bitstring_to_list(<<1:800,2,3,4,1:1>>)), - ?line [1,2,3,4|_Rest1] = bitstring_to_list(<<1,2,3,4,1:800,1:1>>), - ?line <<1:801,1,2,3,4>> = list_to_bitstring([<<1:801>>,1,2,3,4]), + [1,2,3,4|_Rest1] = bitstring_to_list(<<1,2,3,4,1:800,1:1>>), + <<1:801,1,2,3,4>> = list_to_bitstring([<<1:801>>,1,2,3,4]), ok. send_and_receive(Config) when is_list(Config) -> - ?line Bin = <<1,2:7>>, + Bin = <<1,2:7>>, Pid = spawn_link(fun() -> receiver(Bin) end), - ?line Pid ! {self(),<<1:7,8:5,Bin/bitstring>>}, - ?line receive - ok -> - ok - end. + Pid ! {self(),<<1:7,8:5,Bin/bitstring>>}, + receive + ok -> + ok + end. receiver(Bin) -> receive diff --git a/lib/compiler/test/bs_construct_SUITE.erl b/lib/compiler/test/bs_construct_SUITE.erl index 87cfaaf73c..d94e870e21 100644 --- a/lib/compiler/test/bs_construct_SUITE.erl +++ b/lib/compiler/test/bs_construct_SUITE.erl @@ -31,9 +31,11 @@ nasty_literals/1,coerce_to_float/1,side_effect/1, opt/1,otp_7556/1,float_arith/1,otp_8054/1]). --include_lib("test_server/include/test_server.hrl"). +-include_lib("common_test/include/ct.hrl"). -suite() -> [{ct_hooks,[ts_install_cth]}]. +suite() -> + [{ct_hooks,[ts_install_cth]}, + {timetrap,{minutes,1}}]. all() -> test_lib:recompile(?MODULE), @@ -60,12 +62,9 @@ end_per_group(_GroupName, Config) -> init_per_testcase(Case, Config) when is_atom(Case), is_list(Config) -> - Dog = test_server:timetrap(?t:minutes(1)), - [{watchdog,Dog}|Config]. + Config. end_per_testcase(Case, Config) when is_atom(Case), is_list(Config) -> - Dog = ?config(watchdog, Config), - ?t:timetrap_cancel(Dog), ok. two(Config) when is_list(Config) -> @@ -86,7 +85,7 @@ id(I) -> I. -define(T(B, L), {B, ??B, L}). -define(N(B), {B, ??B, unknown}). --define(FAIL(Expr), ?line {'EXIT',{badarg,_}} = (catch Expr)). +-define(FAIL(Expr), {'EXIT',{badarg,_}} = (catch Expr)). l(I_13, I_big1, I_16, Bin) -> [ @@ -200,7 +199,7 @@ one_test({C_bin, E_bin, Str, Bytes}) when is_list(Bytes) -> true -> io:format("ERROR: Compiled: ~p. Expected ~p. Got ~p.~n", [Str, Bytes, bitstring_to_list(C_bin)]), - test_server:fail(comp) + ct:fail(comp) end, if E_bin == Bin -> @@ -208,7 +207,7 @@ one_test({C_bin, E_bin, Str, Bytes}) when is_list(Bytes) -> true -> io:format("ERROR: Interpreted: ~p. Expected ~p. Got ~p.~n", [Str, Bytes, bitstring_to_list(E_bin)]), - test_server:fail(comp) + ct:fail(comp) end; one_test({C_bin, E_bin, Str, Result}) -> io:format(" ~s ~p~n", [Str, C_bin]), @@ -229,7 +228,7 @@ one_test({C_bin, E_bin, Str, Result}) -> io:format("ERROR: Compiled not equal to interpreted:" "~n ~p, ~p.~n", [bitstring_to_list(C_bin), bitstring_to_list(E_bin)]), - test_server:fail(comp); + ct:fail(comp); 0 -> ok; %% For situations where the final bits may not matter, like @@ -261,15 +260,15 @@ equal_lists(A, B, R) -> end. test1(Config) when is_list(Config) -> - ?line I_13 = i(13), - ?line I_big1 = big(1), - ?line I_16 = i(16), - ?line Bin = i(<<16#A5,16#5A,16#C3>>), - ?line Vars = lists:sort([{'I_13',I_13}, - {'I_big1',I_big1}, - {'I_16',I_16}, - {'Bin',Bin}]), - ?line lists:foreach(fun one_test/1, eval_list(l(I_13, I_big1, I_16, Bin), Vars)). + I_13 = i(13), + I_big1 = big(1), + I_16 = i(16), + Bin = i(<<16#A5,16#5A,16#C3>>), + Vars = lists:sort([{'I_13',I_13}, + {'I_big1',I_big1}, + {'I_16',I_16}, + {'Bin',Bin}]), + lists:foreach(fun one_test/1, eval_list(l(I_13, I_big1, I_16, Bin), Vars)). fail(Config) when is_list(Config) -> I_minus_777 = i(-777), @@ -278,68 +277,68 @@ fail(Config) when is_list(Config) -> %% One negative field size, but the sum of field sizes will be 1 byte. %% Make sure that we reject that properly. - ?line {'EXIT',{badarg,_}} = (catch <<I_minus_777:2048/unit:8, - 57:I_minus_2047/unit:8>>), + {'EXIT',{badarg,_}} = (catch <<I_minus_777:2048/unit:8, + 57:I_minus_2047/unit:8>>), %% Same thing, but use literals. - ?line {'EXIT',{badarg,_}} = (catch <<I_minus_777:2048/unit:8, - 57:(-2047)/unit:8>>), + {'EXIT',{badarg,_}} = (catch <<I_minus_777:2048/unit:8, + 57:(-2047)/unit:8>>), %% Not numbers. - ?line {'EXIT',{badarg,_}} = (catch <<45:(i(not_a_number))>>), - ?line {'EXIT',{badarg,_}} = (catch <<13:8,45:(i(not_a_number))>>), + {'EXIT',{badarg,_}} = (catch <<45:(i(not_a_number))>>), + {'EXIT',{badarg,_}} = (catch <<13:8,45:(i(not_a_number))>>), %% Unaligned sizes. BadSz = i(7), Bitstr = i(<<42:17>>), - ?line {'EXIT',{badarg,_}} = (catch <<Bitstr:4/binary>>), - ?line {'EXIT',{badarg,_}} = (catch <<Bitstr:BadSz/binary>>), + {'EXIT',{badarg,_}} = (catch <<Bitstr:4/binary>>), + {'EXIT',{badarg,_}} = (catch <<Bitstr:BadSz/binary>>), - ?line [] = [X || {X} <- [], X == <<Bitstr:BadSz/binary>>], - ?line [] = [X || {X} <- [], X == <<Bitstr:4/binary>>], + [] = [X || {X} <- [], X == <<Bitstr:BadSz/binary>>], + [] = [X || {X} <- [], X == <<Bitstr:4/binary>>], %% Literals with incorrect type. - ?line {'EXIT',{badarg,_}} = (catch <<42.0/integer>>), - ?line {'EXIT',{badarg,_}} = (catch <<42/binary>>), - ?line {'EXIT',{badarg,_}} = (catch <<an_atom/integer>>), + {'EXIT',{badarg,_}} = (catch <<42.0/integer>>), + {'EXIT',{badarg,_}} = (catch <<42/binary>>), + {'EXIT',{badarg,_}} = (catch <<an_atom/integer>>), ok. float_bin(Config) when is_list(Config) -> %% Some more coverage. - ?line {<<1,2,3>>,7.0} = float_bin_1(4), + {<<1,2,3>>,7.0} = float_bin_1(4), F = 42.0, - ?line <<42,0,0,0,0,0,0,69,64>> = <<(id(42)),F/little-float>>, + <<42,0,0,0,0,0,0,69,64>> = <<(id(42)),F/little-float>>, ok. float_bin_1(F) -> {<<1,2,3>>,F+3.0}. in_guard(Config) when is_list(Config) -> - ?line 1 = in_guard_1(<<16#74ad:16>>, 16#e95, 5), - ?line 2 = in_guard_1(<<16#3A,16#F7,"hello">>, 16#3AF7, <<"hello">>), - ?line 3 = in_guard_1(<<16#FBCD:14,3.1415/float,3:2>>, 16#FBCD, 3.1415), - ?line 3 = in_guard_1(<<16#FBCD:14,3/float,3:2>>, 16#FBCD, 3), - ?line 3 = in_guard_1(<<16#FBCD:14,(2 bsl 226)/float,3:2>>, 16#FBCD, 2 bsl 226), - ?line nope = in_guard_1(<<1>>, 42, b), - ?line nope = in_guard_1(<<1>>, a, b), - ?line nope = in_guard_1(<<1,2>>, 1, 1), - ?line nope = in_guard_1(<<4,5>>, 1, 2.71), - ?line nope = in_guard_1(<<4,5>>, 1, <<12,13>>), - - ?line 1 = in_guard_2(<<0,56>>, 7, blurf), - ?line 2 = in_guard_2(<<1,255>>, 511, blurf), - ?line 3 = in_guard_2(<<0,3>>, 0, blurf), - ?line 4 = in_guard_2(<<>>, 1, {<<7:16>>}), - ?line nope = in_guard_2(<<4,5>>, 1, blurf), - - ?line 42 = in_guard_3(<<1,2,3,42>>, <<1,2,3>>), - ?line 42 = in_guard_3(<<1,2,3,42>>, <<1,2,3>>), - ?line nope = in_guard_3(<<>>, <<>>), - - ?line ok = in_guard_4(<<15:4>>, 255), - ?line nope = in_guard_4(<<15:8>>, 255), + 1 = in_guard_1(<<16#74ad:16>>, 16#e95, 5), + 2 = in_guard_1(<<16#3A,16#F7,"hello">>, 16#3AF7, <<"hello">>), + 3 = in_guard_1(<<16#FBCD:14,3.1415/float,3:2>>, 16#FBCD, 3.1415), + 3 = in_guard_1(<<16#FBCD:14,3/float,3:2>>, 16#FBCD, 3), + 3 = in_guard_1(<<16#FBCD:14,(2 bsl 226)/float,3:2>>, 16#FBCD, 2 bsl 226), + nope = in_guard_1(<<1>>, 42, b), + nope = in_guard_1(<<1>>, a, b), + nope = in_guard_1(<<1,2>>, 1, 1), + nope = in_guard_1(<<4,5>>, 1, 2.71), + nope = in_guard_1(<<4,5>>, 1, <<12,13>>), + + 1 = in_guard_2(<<0,56>>, 7, blurf), + 2 = in_guard_2(<<1,255>>, 511, blurf), + 3 = in_guard_2(<<0,3>>, 0, blurf), + 4 = in_guard_2(<<>>, 1, {<<7:16>>}), + nope = in_guard_2(<<4,5>>, 1, blurf), + + 42 = in_guard_3(<<1,2,3,42>>, <<1,2,3>>), + 42 = in_guard_3(<<1,2,3,42>>, <<1,2,3>>), + nope = in_guard_3(<<>>, <<>>), + + ok = in_guard_4(<<15:4>>, 255), + nope = in_guard_4(<<15:8>>, 255), ok. in_guard_1(Bin, A, B) when <<A:13,B:3>> == Bin -> 1; @@ -361,10 +360,10 @@ in_guard_4(Bin, A) when <<A:4>> =:= Bin -> ok; in_guard_4(_, _) -> nope. in_catch(Config) when is_list(Config) -> - ?line <<42,0,5>> = small(42, 5), - ?line <<255>> = small(255, <<1,2,3,4,5,6,7,8,9>>), - ?line <<1,2>> = small(<<7,8,9,10>>, 258), - ?line <<>> = small(<<1,2,3,4,5>>, <<7,8,9,10>>), + <<42,0,5>> = small(42, 5), + <<255>> = small(255, <<1,2,3,4,5,6,7,8,9>>), + <<1,2>> = small(<<7,8,9,10>>, 258), + <<>> = small(<<1,2,3,4,5>>, <<7,8,9,10>>), <<15,240,0,42>> = small2(255, 42), <<7:20>> = small2(<<1,2,3>>, 7), @@ -413,20 +412,20 @@ small2(A, B) -> nasty_literals(Config) when is_list(Config) -> case erlang:system_info(endian) of big -> - ?line [0,42] = binary_to_list(id(<<42:16/native>>)); + [0,42] = binary_to_list(id(<<42:16/native>>)); little -> - ?line [42,0] = binary_to_list(id(<<42:16/native>>)) + [42,0] = binary_to_list(id(<<42:16/native>>)) end, - ?line Bin0 = id(<<1,2,3,0:10000000,4,5,6>>), - ?line 1250006 = size(Bin0), - ?line <<1,2,3,0:10000000,4,5,6>> = Bin0, + Bin0 = id(<<1,2,3,0:10000000,4,5,6>>), + 1250006 = size(Bin0), + <<1,2,3,0:10000000,4,5,6>> = Bin0, - ?line Bin1 = id(<<0:10000000,7,8,-1:10000000,9,10,0:10000000>>), - ?line 3750004 = size(Bin1), - ?line <<0:10000000,7,8,-1:10000000/signed,9,10,0:10000000>> = Bin1, + Bin1 = id(<<0:10000000,7,8,-1:10000000,9,10,0:10000000>>), + 3750004 = size(Bin1), + <<0:10000000,7,8,-1:10000000/signed,9,10,0:10000000>> = Bin1, - ?line <<255,255,0,0,0>> = id(<<255,255,0,0,0>>), + <<255,255,0,0,0>> = id(<<255,255,0,0,0>>), %% Coverage. I = 16#7777FFFF7777FFFF7777FFFF7777FFFF7777FFFF7777FFFF, @@ -435,18 +434,18 @@ nasty_literals(Config) when is_list(Config) -> ok. -define(COF(Int0), - ?line (fun(Int) -> - true = <<Int:32/float>> =:= <<(float(Int)):32/float>>, - true = <<Int:64/float>> =:= <<(float(Int)):64/float>> - end)(nonliteral(Int0)), - ?line true = <<Int0:32/float>> =:= <<(float(Int0)):32/float>>, - ?line true = <<Int0:64/float>> =:= <<(float(Int0)):64/float>>). + (fun(Int) -> + true = <<Int:32/float>> =:= <<(float(Int)):32/float>>, + true = <<Int:64/float>> =:= <<(float(Int)):64/float>> + end)(nonliteral(Int0)), + true = <<Int0:32/float>> =:= <<(float(Int0)):32/float>>, + true = <<Int0:64/float>> =:= <<(float(Int0)):64/float>>). -define(COF64(Int0), - ?line (fun(Int) -> - true = <<Int:64/float>> =:= <<(float(Int)):64/float>> - end)(nonliteral(Int0)), - ?line true = <<Int0:64/float>> =:= <<(float(Int0)):64/float>>). + (fun(Int) -> + true = <<Int:64/float>> =:= <<(float(Int)):64/float>> + end)(nonliteral(Int0)), + true = <<Int0:64/float>> =:= <<(float(Int0)):64/float>>). nonliteral(X) -> X. @@ -467,7 +466,7 @@ coerce_to_float(Config) when is_list(Config) -> side_effect(Config) when is_list(Config) -> {'EXIT',{badarg,_}} = (catch side_effect_1(a)), {'EXIT',{badarg,_}} = (catch side_effect_1(<<>>)), - ?line ok = side_effect_1(42), + ok = side_effect_1(42), ok. side_effect_1(A) -> @@ -477,32 +476,32 @@ side_effect_1(A) -> -record(otp_7029, {a,b}). opt(Config) when is_list(Config) -> - ?line 42 = otp_7029(#otp_7029{a = <<>>,b = 42}), + 42 = otp_7029(#otp_7029{a = <<>>,b = 42}), N = 16, - ?line <<1,3,65>> = id(<<1,833:N>>), - ?line <<1,66,3>> = id(<<1,834:N/little>>), - ?line <<1,65,136,0,0>> = id(<<1,17.0:32/float>>), - ?line <<1,64,8,0,0,0,0,0,0>> = id(<<1,3.0:N/float-unit:4>>), - ?line <<1,0,0,0,0,0,0,8,64>> = id(<<1,3.0:N/little-float-unit:4>>), - ?line {'EXIT',{badarg,_}} = (catch id(<<3.1416:N/float>>)), + <<1,3,65>> = id(<<1,833:N>>), + <<1,66,3>> = id(<<1,834:N/little>>), + <<1,65,136,0,0>> = id(<<1,17.0:32/float>>), + <<1,64,8,0,0,0,0,0,0>> = id(<<1,3.0:N/float-unit:4>>), + <<1,0,0,0,0,0,0,8,64>> = id(<<1,3.0:N/little-float-unit:4>>), + {'EXIT',{badarg,_}} = (catch id(<<3.1416:N/float>>)), B = <<1,2,3,4,5>>, - ?line <<0,1,2,3,4,5>> = id(<<0,B/binary>>), - ?line <<1,2,3,4,5,19>> = id(<<B:5/binary,19>>), - ?line <<1,2,3,42>> = id(<<B:3/binary,42>>), + <<0,1,2,3,4,5>> = id(<<0,B/binary>>), + <<1,2,3,4,5,19>> = id(<<B:5/binary,19>>), + <<1,2,3,42>> = id(<<B:3/binary,42>>), - ?line {'EXIT',_} = (catch <<<<23,56,0,2>>:(2.5)/binary>>), - ?line {'EXIT',_} = (catch <<<<23,56,0,2>>:(-16)/binary>>), - ?line {'EXIT',_} = (catch <<<<23,56,0,2>>:(anka)>>), - ?line {'EXIT',_} = (catch <<<<23,56,0,2>>:64/float>>), - ?line {'EXIT',_} = (catch <<<<23,56,0,2:7>>/binary>>), + {'EXIT',_} = (catch <<<<23,56,0,2>>:(2.5)/binary>>), + {'EXIT',_} = (catch <<<<23,56,0,2>>:(-16)/binary>>), + {'EXIT',_} = (catch <<<<23,56,0,2>>:(anka)>>), + {'EXIT',_} = (catch <<<<23,56,0,2>>:64/float>>), + {'EXIT',_} = (catch <<<<23,56,0,2:7>>/binary>>), %% Test constant propagation - there should be a warning. BadSz = 2.5, {'EXIT',_} = (catch <<<<N,56,0,2>>:BadSz/binary>>), case id(false) of - true -> ?line opt_dont_call_me(); + true -> opt_dont_call_me(); false -> ok end, @@ -530,7 +529,7 @@ otp_7556(Bin, A, B, C) -> %% for a binary construction with a later allocation). float_arith(Config) when is_list(Config) -> - ?line {<<1,2,3,64,69,0,0,0,0,0,0>>,21.0} = do_float_arith(<<1,2,3>>, 42, 2), + {<<1,2,3,64,69,0,0,0,0,0,0>>,21.0} = do_float_arith(<<1,2,3>>, 42, 2), ok. do_float_arith(Bin0, X, Y) -> @@ -538,7 +537,7 @@ do_float_arith(Bin0, X, Y) -> {Bin,X / Y}. otp_8054(Config) when is_list(Config) -> - ?line <<"abc">> = otp_8054_1([null,1,2,3], <<"abc">>), + <<"abc">> = otp_8054_1([null,1,2,3], <<"abc">>), ok. otp_8054_1([H|T], Bin) -> diff --git a/lib/compiler/test/bs_match_SUITE.erl b/lib/compiler/test/bs_match_SUITE.erl index 7fb0a16540..7fa26b6c26 100644 --- a/lib/compiler/test/bs_match_SUITE.erl +++ b/lib/compiler/test/bs_match_SUITE.erl @@ -36,15 +36,19 @@ match_string/1,zero_width/1,bad_size/1,haystack/1, cover_beam_bool/1,matched_out_size/1,follow_fail_branch/1, no_partition/1,calling_a_binary/1,binary_in_map/1, - match_string_opt/1,map_and_binary/1, - unsafe_branch_caching/1]). + match_string_opt/1,select_on_integer/1, + map_and_binary/1,unsafe_branch_caching/1, + bad_literals/1,good_literals/1]). -export([coverage_id/1,coverage_external_ignore/2]). --include_lib("test_server/include/test_server.hrl"). +-include_lib("common_test/include/ct.hrl"). +-include_lib("syntax_tools/include/merl.hrl"). -suite() -> [{ct_hooks,[ts_install_cth]}]. +suite() -> + [{ct_hooks,[ts_install_cth]}, + {timetrap,{minutes,1}}]. all() -> test_lib:recompile(?MODULE), @@ -63,8 +67,9 @@ groups() -> otp_7498,match_string,zero_width,bad_size,haystack, cover_beam_bool,matched_out_size,follow_fail_branch, no_partition,calling_a_binary,binary_in_map, - match_string_opt,map_and_binary, - unsafe_branch_caching]}]. + match_string_opt,select_on_integer, + map_and_binary,unsafe_branch_caching, + bad_literals,good_literals]}]. init_per_suite(Config) -> @@ -81,20 +86,17 @@ end_per_group(_GroupName, Config) -> init_per_testcase(Case, Config) when is_atom(Case), is_list(Config) -> - Dog = test_server:timetrap(?t:minutes(1)), - [{watchdog,Dog}|Config]. + Config. end_per_testcase(Case, Config) when is_atom(Case), is_list(Config) -> - Dog = ?config(watchdog, Config), - ?t:timetrap_cancel(Dog), ok. fun_shadow(Config) when is_list(Config) -> %% OTP-5270 - ?line 7 = fun_shadow_1(), - ?line 7 = fun_shadow_2(8), - ?line 7 = fun_shadow_3(), - ?line no = fun_shadow_4(8), + 7 = fun_shadow_1(), + 7 = fun_shadow_2(8), + 7 = fun_shadow_3(), + no = fun_shadow_4(8), ok. fun_shadow_1() -> @@ -118,71 +120,78 @@ fun_shadow_4(L) -> int_float(Config) when is_list(Config) -> %% OTP-5323 - ?line <<103133.0:64/float>> = <<103133:64/float>>, - ?line <<103133:64/float>> = <<103133:64/float>>, - ok. + <<103133.0:64/float>> = <<103133:64/float>>, + <<103133:64/float>> = <<103133:64/float>>, + + %% Coverage of error cases in sys_pre_expand:coerce_to_float/2. + case id(default) of + <<(1 bsl 1024):64/float>> -> + ct:fail(should_not_match); + default -> + ok + end. %% Stolen from erl_eval_SUITE and modified. %% OTP-5269. Bugs in the bit syntax. otp_5269(Config) when is_list(Config) -> - ?line check(fun() -> L = 8, - F = fun(<<A:L,B:A>>) -> B end, - F(<<16:8, 7:16>>) + check(fun() -> L = 8, + F = fun(<<A:L,B:A>>) -> B end, + F(<<16:8, 7:16>>) end, 7), - ?line check(fun() -> L = 8, <<A:L,B:A>> = <<16:8, 7:16>>, B end, - 7), - ?line check(fun() -> U = 8, (fun(<<U:U>>) -> U end)(<<32:8>>) end, - 32), - ?line check(fun() -> U = 8, [U || <<U:U>> <- [<<32:8>>]] end, - [32]), - ?line check(fun() -> [X || <<A:8, - B:A>> <- [<<16:8,19:16>>], - <<X:8>> <- [<<B:8>>]] end, - [19]), - ?line check(fun() -> A = 4, B = 28, bit_size(<<13:(A+(X=B))>>), X end, - 28), - ?line check(fun() -> - <<Size,B:Size/binary,Rest/binary>> = <<2,"AB","CD">>, - {Size,B,Rest} - end, - {2,<<"AB">>,<<"CD">>}), - ?line check(fun() -> X = 32, - [X || <<X:X>> <- [<<1:32>>,<<2:32>>,<<3:8>>]] end, - %% "binsize variable" ^ - [1,2]), - ?line check(fun() -> - (fun (<<A:1/binary, B:8/integer, _C:B/binary>>) -> - case A of - B -> wrong; - _ -> ok - end - end)(<<1,2,3,4>>) end, - ok), + check(fun() -> L = 8, <<A:L,B:A>> = <<16:8, 7:16>>, B end, + 7), + check(fun() -> U = 8, (fun(<<U:U>>) -> U end)(<<32:8>>) end, + 32), + check(fun() -> U = 8, [U || <<U:U>> <- [<<32:8>>]] end, + [32]), + check(fun() -> [X || <<A:8, + B:A>> <- [<<16:8,19:16>>], + <<X:8>> <- [<<B:8>>]] end, + [19]), + check(fun() -> A = 4, B = 28, bit_size(<<13:(A+(X=B))>>), X end, + 28), + check(fun() -> + <<Size,B:Size/binary,Rest/binary>> = <<2,"AB","CD">>, + {Size,B,Rest} + end, + {2,<<"AB">>,<<"CD">>}), + check(fun() -> X = 32, + [X || <<X:X>> <- [<<1:32>>,<<2:32>>,<<3:8>>]] end, + %% "binsize variable" ^ + [1,2]), + check(fun() -> + (fun (<<A:1/binary, B:8/integer, _C:B/binary>>) -> + case A of + B -> wrong; + _ -> ok + end + end)(<<1,2,3,4>>) end, + ok), ok. null_fields(Config) when is_list(Config) -> - ?line check(fun() -> - W = id(0), - F = fun(<<_:W>>) -> tail; - (<<>>) -> empty - end, - F(<<>>) - end, tail), - ?line check(fun() -> - F = fun(<<_/binary>>) -> tail; - (<<>>) -> empty - end, - F(<<>>) - end, tail), + check(fun() -> + W = id(0), + F = fun(<<_:W>>) -> tail; + (<<>>) -> empty + end, + F(<<>>) + end, tail), + check(fun() -> + F = fun(<<_/binary>>) -> tail; + (<<>>) -> empty + end, + F(<<>>) + end, tail), ok. wiger(Config) when is_list(Config) -> - ?line ok1 = wcheck(<<3>>), - ?line ok2 = wcheck(<<1,2,3>>), - ?line ok3 = wcheck(<<4>>), - ?line {error,<<1,2,3,4>>} = wcheck(<<1,2,3,4>>), - ?line {error,<<>>} = wcheck(<<>>), + ok1 = wcheck(<<3>>), + ok2 = wcheck(<<1,2,3>>), + ok3 = wcheck(<<4>>), + {error,<<1,2,3,4>>} = wcheck(<<1,2,3,4>>), + {error,<<>>} = wcheck(<<>>), ok. wcheck(<<A>>) when A==3-> @@ -196,24 +205,24 @@ wcheck(Other) -> bin_tail(Config) when is_list(Config) -> S = <<"abcde">>, - ?line $a = bin_tail_c(S, 0), - ?line $c = bin_tail_c(S, 2), - ?line $e = bin_tail_c(S, 4), - ?line {'EXIT',_} = (catch bin_tail_c(S, 5)), - ?line {'EXIT',_} = (catch bin_tail_c_var(S, 5)), - - ?line $a = bin_tail_d(S, 0), - ?line $b = bin_tail_d(S, 8), - ?line $d = bin_tail_d(S, 3*8), - ?line {'EXIT',_} = (catch bin_tail_d_dead(S, 1)), - ?line {'EXIT',_} = (catch bin_tail_d_dead(S, 9)), - ?line {'EXIT',_} = (catch bin_tail_d_dead(S, 5*8)), - ?line {'EXIT',_} = (catch bin_tail_d_var(S, 1)), - - ?line ok = bin_tail_e(<<2:2,0:1,1:5>>), - ?line ok = bin_tail_e(<<2:2,1:1,1:5,42:64>>), - ?line error = bin_tail_e(<<3:2,1:1,1:5,42:64>>), - ?line error = bin_tail_e(<<>>), + $a = bin_tail_c(S, 0), + $c = bin_tail_c(S, 2), + $e = bin_tail_c(S, 4), + {'EXIT',_} = (catch bin_tail_c(S, 5)), + {'EXIT',_} = (catch bin_tail_c_var(S, 5)), + + $a = bin_tail_d(S, 0), + $b = bin_tail_d(S, 8), + $d = bin_tail_d(S, 3*8), + {'EXIT',_} = (catch bin_tail_d_dead(S, 1)), + {'EXIT',_} = (catch bin_tail_d_dead(S, 9)), + {'EXIT',_} = (catch bin_tail_d_dead(S, 5*8)), + {'EXIT',_} = (catch bin_tail_d_var(S, 1)), + + ok = bin_tail_e(<<2:2,0:1,1:5>>), + ok = bin_tail_e(<<2:2,1:1,1:5,42:64>>), + error = bin_tail_e(<<3:2,1:1,1:5,42:64>>), + error = bin_tail_e(<<>>), ok. bin_tail_c(Bin, Offset) -> @@ -272,34 +281,34 @@ bin_tail_e_var(Bin) -> end. save_restore(Config) when is_list(Config) -> - ?line 0 = save_restore_1(<<0:2,42:6>>), - ?line {1,3456} = save_restore_1(<<1:2,3456:14>>), - ?line {2,7981234} = save_restore_1(<<2:2,7981234:30>>), - ?line {3,763967493838} = save_restore_1(<<0:2,763967493838:62>>), + 0 = save_restore_1(<<0:2,42:6>>), + {1,3456} = save_restore_1(<<1:2,3456:14>>), + {2,7981234} = save_restore_1(<<2:2,7981234:30>>), + {3,763967493838} = save_restore_1(<<0:2,763967493838:62>>), A = <<" x">>, B = <<".x">>, C = <<"-x">>, - ?line {" ",<<"x">>} = lll(A), - ?line {" ",<<"x">>} = mmm(A), - ?line {" ",<<"x">>} = nnn(A), - ?line {" ",<<"x">>} = ooo(A), + {" ",<<"x">>} = lll(A), + {" ",<<"x">>} = mmm(A), + {" ",<<"x">>} = nnn(A), + {" ",<<"x">>} = ooo(A), - ?line {".",<<"x">>} = lll(B), - ?line {".",<<"x">>} = mmm(B), - ?line {".",<<"x">>} = nnn(B), - ?line {".",<<"x">>} = ooo(B), + {".",<<"x">>} = lll(B), + {".",<<"x">>} = mmm(B), + {".",<<"x">>} = nnn(B), + {".",<<"x">>} = ooo(B), - ?line {"-",<<"x">>} = lll(C), - ?line {"-",<<"x">>} = mmm(C), - ?line {"-",<<"x">>} = nnn(C), - ?line {"-",<<"x">>} = ooo(C), + {"-",<<"x">>} = lll(C), + {"-",<<"x">>} = mmm(C), + {"-",<<"x">>} = nnn(C), + {"-",<<"x">>} = ooo(C), Bin = <<-1:64>>, case bad_float_unpack_match(Bin) of -1 -> ok; - _Other -> ?line ?t:fail(bad_return_value_probably_NaN) + _Other -> ct:fail(bad_return_value_probably_NaN) end. save_restore_1(Bin) -> @@ -328,18 +337,18 @@ bad_float_unpack_match(<<I:64/integer-signed>>) -> I. partitioned_bs_match(Config) when is_list(Config) -> - ?line <<1,2,3>> = partitioned_bs_match(blurf, <<42,1,2,3>>), - ?line error = partitioned_bs_match(10, <<7,8,15,13>>), - ?line error = partitioned_bs_match(100, {a,tuple,is,'not',a,binary}), - ?line ok = partitioned_bs_match(0, <<>>), - ?line fc(partitioned_bs_match, [-1,blurf], + <<1,2,3>> = partitioned_bs_match(blurf, <<42,1,2,3>>), + error = partitioned_bs_match(10, <<7,8,15,13>>), + error = partitioned_bs_match(100, {a,tuple,is,'not',a,binary}), + ok = partitioned_bs_match(0, <<>>), + fc(partitioned_bs_match, [-1,blurf], catch partitioned_bs_match(-1, blurf)), - ?line fc(partitioned_bs_match, [-1,<<1,2,3>>], + fc(partitioned_bs_match, [-1,<<1,2,3>>], catch partitioned_bs_match(-1, <<1,2,3>>)), - ?line {17,<<1,2,3>>} = partitioned_bs_match_2(1, <<17,1,2,3>>), - ?line {7,<<1,2,3>>} = partitioned_bs_match_2(7, <<17,1,2,3>>), + {17,<<1,2,3>>} = partitioned_bs_match_2(1, <<17,1,2,3>>), + {7,<<1,2,3>>} = partitioned_bs_match_2(7, <<17,1,2,3>>), - ?line fc(partitioned_bs_match_2, [4,<<0:17>>], + fc(partitioned_bs_match_2, [4,<<0:17>>], catch partitioned_bs_match_2(4, <<0:17>>)), anything = partitioned_bs_match_3(anything, <<42>>), @@ -392,25 +401,25 @@ function_clause_2(<<_:4>>) -> ok. unit(Config) when is_list(Config) -> - ?line 42 = peek1(<<42>>), - ?line 43 = peek1(<<43,1,2>>), - ?line 43 = peek1(<<43,1,2,(-1):1>>), - ?line 43 = peek1(<<43,1,2,(-1):2>>), - ?line 43 = peek1(<<43,1,2,(-1):7>>), - - ?line 99 = peek8(<<99>>), - ?line 100 = peek8(<<100,101>>), - ?line fc(peek8, [<<100,101,0:1>>], catch peek8(<<100,101,0:1>>)), - - ?line 37484 = peek16(<<37484:16>>), - ?line 37489 = peek16(<<37489:16,5566:16>>), - ?line fc(peek16, [<<8>>], catch peek16(<<8>>)), - ?line fc(peek16, [<<42:15>>], catch peek16(<<42:15>>)), - ?line fc(peek16, [<<1,2,3,4,5>>], catch peek16(<<1,2,3,4,5>>)), - - ?line 127 = peek7(<<127:7>>), - ?line 100 = peek7(<<100:7,19:7>>), - ?line fc(peek7, [<<1,2>>], catch peek7(<<1,2>>)), + 42 = peek1(<<42>>), + 43 = peek1(<<43,1,2>>), + 43 = peek1(<<43,1,2,(-1):1>>), + 43 = peek1(<<43,1,2,(-1):2>>), + 43 = peek1(<<43,1,2,(-1):7>>), + + 99 = peek8(<<99>>), + 100 = peek8(<<100,101>>), + fc(peek8, [<<100,101,0:1>>], catch peek8(<<100,101,0:1>>)), + + 37484 = peek16(<<37484:16>>), + 37489 = peek16(<<37489:16,5566:16>>), + fc(peek16, [<<8>>], catch peek16(<<8>>)), + fc(peek16, [<<42:15>>], catch peek16(<<42:15>>)), + fc(peek16, [<<1,2,3,4,5>>], catch peek16(<<1,2,3,4,5>>)), + + 127 = peek7(<<127:7>>), + 100 = peek7(<<100:7,19:7>>), + fc(peek7, [<<1,2>>], catch peek7(<<1,2>>)), ok. peek1(<<B:8,_/bitstring>>) -> B. @@ -422,7 +431,7 @@ peek8(<<B:8,_/binary>>) -> B. peek16(<<B:16,_/binary-unit:16>>) -> B. shared_sub_bins(Config) when is_list(Config) -> - ?line {15,[<<>>,<<5>>,<<4,5>>,<<3,4,5>>,<<2,3,4,5>>]} = sum(<<1,2,3,4,5>>, [], 0), + {15,[<<>>,<<5>>,<<4,5>>,<<3,4,5>>,<<2,3,4,5>>]} = sum(<<1,2,3,4,5>>, [], 0), ok. sum(<<B,T/binary>>, Acc, Sum) -> @@ -431,7 +440,7 @@ sum(<<>>, Last, Sum) -> {Sum,Last}. bin_and_float(Config) when is_list(Config) -> - ?line 14.0 = bin_and_float(<<1.0/float,2.0/float,3.0/float>>, 0.0), + 14.0 = bin_and_float(<<1.0/float,2.0/float,3.0/float>>, 0.0), ok. bin_and_float(<<X/float,Y/float,Z/float,T/binary>>, Sum) when is_float(X), @@ -441,10 +450,10 @@ bin_and_float(<<X/float,Y/float,Z/float,T/binary>>, Sum) when is_float(X), bin_and_float(<<>>, Sum) -> Sum. dec_subidentifiers(Config) when is_list(Config) -> - ?line {[],<<1,2,3>>} = + {[],<<1,2,3>>} = do_dec_subidentifiers(<<1:1,42:7,1:1,99:7,1,2,3>>, 0, [], 2), - ?line {[5389],<<1,2,3>>} = do_dec_subidentifiers(<<1:1,42:7,0:1,13:7,1,2,3>>, 0, [], 2), - ?line {[3,2,1],not_a_binary} = dec_subidentifiers(not_a_binary, any, [1,2,3], 0), + {[5389],<<1,2,3>>} = do_dec_subidentifiers(<<1:1,42:7,0:1,13:7,1,2,3>>, 0, [], 2), + {[3,2,1],not_a_binary} = dec_subidentifiers(not_a_binary, any, [1,2,3], 0), ok. do_dec_subidentifiers(Buffer, Av, Al, Len) -> @@ -500,18 +509,18 @@ skip_optional_tag(_, _) -> missing. wfbm(Config) when is_list(Config) -> %% check_for_dot_or_space and get_tail is from wfbm4 by Steve Vinoski, %% with modifications. - ?line {nomatch,0} = check_for_dot_or_space(<<" ">>), - ?line {nomatch,0} = check_for_dot_or_space(<<" abc">>), - ?line {ok,<<"abcde">>} = check_for_dot_or_space(<<"abcde 34555">>), - ?line {nomatch,0} = check_for_dot_or_space(<<".gurka">>), - ?line {nomatch,1} = check_for_dot_or_space(<<"g.urka">>), - - ?line nomatch = get_tail(<<>>), - ?line {ok,<<"2007/10/23/blurf">>} = get_tail(<<"200x/2007/10/23/blurf ">>), - ?line {skip,?DATELEN+5} = get_tail(<<"200x/2007/10/23/blurf.">>), - ?line nomatch = get_tail(<<"200y.2007.10.23.blurf ">>), - ?line {'EXIT',_} = (catch get_tail({no,binary,at,all})), - ?line {'EXIT',_} = (catch get_tail(no_binary)), + {nomatch,0} = check_for_dot_or_space(<<" ">>), + {nomatch,0} = check_for_dot_or_space(<<" abc">>), + {ok,<<"abcde">>} = check_for_dot_or_space(<<"abcde 34555">>), + {nomatch,0} = check_for_dot_or_space(<<".gurka">>), + {nomatch,1} = check_for_dot_or_space(<<"g.urka">>), + + nomatch = get_tail(<<>>), + {ok,<<"2007/10/23/blurf">>} = get_tail(<<"200x/2007/10/23/blurf ">>), + {skip,?DATELEN+5} = get_tail(<<"200x/2007/10/23/blurf.">>), + nomatch = get_tail(<<"200y.2007.10.23.blurf ">>), + {'EXIT',_} = (catch get_tail({no,binary,at,all})), + {'EXIT',_} = (catch get_tail(no_binary)), ok. check_for_dot_or_space(Bin) -> @@ -544,13 +553,13 @@ get_tail(Bin) -> end. degenerated_match(Config) when is_list(Config) -> - ?line error = degenerated_match_1(<<>>), - ?line 1 = degenerated_match_1(<<1:1>>), - ?line 2 = degenerated_match_1(<<42,43>>), + error = degenerated_match_1(<<>>), + 1 = degenerated_match_1(<<1:1>>), + 2 = degenerated_match_1(<<42,43>>), - ?line error = degenerated_match_2(<<>>), - ?line no_split = degenerated_match_2(<<1,2>>), - ?line {<<1,2,3,4>>,<<5>>} = degenerated_match_2(<<1,2,3,4,5>>), + error = degenerated_match_2(<<>>), + no_split = degenerated_match_2(<<1,2>>), + {<<1,2,3,4>>,<<5>>} = degenerated_match_2(<<1,2,3,4,5>>), ok. @@ -567,25 +576,25 @@ degenerated_match_2(Bin) -> end. bs_sum(Config) when is_list(Config) -> - ?line 0 = bs_sum_1([]), - ?line 0 = bs_sum_1(<<>>), - ?line 42 = bs_sum_1([42]), - ?line 1 = bs_sum_1(<<1>>), - ?line 10 = bs_sum_1([1,2,3,4]), - ?line 15 = bs_sum_1(<<1,2,3,4,5>>), - ?line 21 = bs_sum_1([1,2,3|<<4,5,6>>]), - ?line 15 = bs_sum_1([1,2,3|{4,5}]), - ?line 6 = bs_sum_1([1,2,3|zero]), - ?line 6 = bs_sum_1([1,2,3|0]), - ?line 7 = bs_sum_1([1,2,3|one]), - - ?line fc(catch bs_sum_1({too,big,tuple})), - ?line fc(catch bs_sum_1([1,2,3|{too,big,tuple}])), - - ?line [] = sneaky_alias(<<>>), - ?line [559,387655] = sneaky_alias(id(<<559:32,387655:32>>)), - ?line fc(sneaky_alias, [<<1>>], catch sneaky_alias(id(<<1>>))), - ?line fc(sneaky_alias, [[1,2,3,4]], catch sneaky_alias(lists:seq(1, 4))), + 0 = bs_sum_1([]), + 0 = bs_sum_1(<<>>), + 42 = bs_sum_1([42]), + 1 = bs_sum_1(<<1>>), + 10 = bs_sum_1([1,2,3,4]), + 15 = bs_sum_1(<<1,2,3,4,5>>), + 21 = bs_sum_1([1,2,3|<<4,5,6>>]), + 15 = bs_sum_1([1,2,3|{4,5}]), + 6 = bs_sum_1([1,2,3|zero]), + 6 = bs_sum_1([1,2,3|0]), + 7 = bs_sum_1([1,2,3|one]), + + fc(catch bs_sum_1({too,big,tuple})), + fc(catch bs_sum_1([1,2,3|{too,big,tuple}])), + + [] = sneaky_alias(<<>>), + [559,387655] = sneaky_alias(id(<<559:32,387655:32>>)), + fc(sneaky_alias, [<<1>>], catch sneaky_alias(id(<<1>>))), + fc(sneaky_alias, [[1,2,3,4]], catch sneaky_alias(lists:seq(1, 4))), ok. bs_sum_1(<<H,T/binary>>) -> H+bs_sum_1(T); @@ -601,31 +610,31 @@ sneaky_alias(<<>>=L) -> binary_to_list(L); sneaky_alias(<<From:32,L/binary>>) -> [From|sneaky_alias(L)]. coverage(Config) when is_list(Config) -> - ?line 0 = coverage_fold(fun(B, A) -> A+B end, 0, <<>>), - ?line 6 = coverage_fold(fun(B, A) -> A+B end, 0, <<1,2,3>>), - ?line fc(catch coverage_fold(fun(B, A) -> + 0 = coverage_fold(fun(B, A) -> A+B end, 0, <<>>), + 6 = coverage_fold(fun(B, A) -> A+B end, 0, <<1,2,3>>), + fc(catch coverage_fold(fun(B, A) -> A+B end, 0, [a,b,c])), - ?line {<<42.0:64/float>>,float} = coverage_build(<<>>, <<42>>, float), - ?line {<<>>,not_a_tuple} = coverage_build(<<>>, <<>>, not_a_tuple), - ?line {<<16#76,"abc",16#A9,"abc">>,{x,42,43}} = + {<<42.0:64/float>>,float} = coverage_build(<<>>, <<42>>, float), + {<<>>,not_a_tuple} = coverage_build(<<>>, <<>>, not_a_tuple), + {<<16#76,"abc",16#A9,"abc">>,{x,42,43}} = coverage_build(<<>>, <<16#7,16#A>>, {x,y,z}), - ?line [<<2>>,<<1>>] = coverage_bc(<<1,2>>, []), + [<<2>>,<<1>>] = coverage_bc(<<1,2>>, []), - ?line {x,<<"abc">>,z} = coverage_setelement(<<2,"abc">>, {x,y,z}), + {x,<<"abc">>,z} = coverage_setelement(<<2,"abc">>, {x,y,z}), - ?line [42] = coverage_apply(<<42>>, [coverage_id]), - ?line 42 = coverage_external(<<42>>), + [42] = coverage_apply(<<42>>, [coverage_id]), + 42 = coverage_external(<<42>>), - ?line do_coverage_bin_to_term_list([]), - ?line do_coverage_bin_to_term_list([lists:seq(0, 10),{a,b,c},<<23:42>>]), - ?line fc(coverage_bin_to_term_list, [<<0,0,0,7>>], + do_coverage_bin_to_term_list([]), + do_coverage_bin_to_term_list([lists:seq(0, 10),{a,b,c},<<23:42>>]), + fc(coverage_bin_to_term_list, [<<0,0,0,7>>], catch do_coverage_bin_to_term_list_1(<<7:32>>)), - ?line <<>> = coverage_per_key(<<4:32>>), - ?line <<$a,$b,$c>> = coverage_per_key(<<7:32,"abc">>), + <<>> = coverage_per_key(<<4:32>>), + <<$a,$b,$c>> = coverage_per_key(<<7:32,"abc">>), ok. @@ -718,9 +727,9 @@ coverage_per_key(<<BinSize:32,Bin/binary>> = B) -> Bin. multiple_uses(Config) when is_list(Config) -> - ?line {344,62879,345,<<245,159,1,89>>} = multiple_uses_1(<<1,88,245,159,1,89>>), - ?line true = multiple_uses_2(<<0,0,197,18>>), - ?line <<42,43>> = multiple_uses_3(<<0,0,42,43>>, fun id/1), + {344,62879,345,<<245,159,1,89>>} = multiple_uses_1(<<1,88,245,159,1,89>>), + true = multiple_uses_2(<<0,0,197,18>>), + <<42,43>> = multiple_uses_3(<<0,0,42,43>>, fun id/1), ok. multiple_uses_1(<<X:16,Tail/binary>>) -> @@ -743,8 +752,8 @@ multiple_uses_cmp(<<Y:16>>, <<Y:16>>) -> true; multiple_uses_cmp(<<_:16>>, <<_:16>>) -> false. zero_label(Config) when is_list(Config) -> - ?line <<"nosemouth">> = read_pols(<<"FACE","nose","mouth">>), - ?line <<"CE">> = read_pols(<<"noFACE">>), + <<"nosemouth">> = read_pols(<<"FACE","nose","mouth">>), + <<"CE">> = read_pols(<<"noFACE">>), ok. read_pols(Data) -> @@ -772,14 +781,14 @@ matching_meets_construction(Config) when is_list(Config) -> Bin = id(<<"abc">>), Len = id(2), Tail0 = id(<<1,2,3,4,5>>), - ?line <<_:Len/binary,Tail/binary>> = Tail0, - ?line Res = <<Tail/binary,Bin/binary>>, - ?line <<3,4,5,"abc">> = Res, - ?line {'EXIT',{badarg,_}} = (catch matching_meets_construction_1(<<"Abc">>)), - ?line {'EXIT',{badarg,_}} = (catch matching_meets_construction_2(<<"Abc">>)), - ?line <<"Bbc">> = matching_meets_construction_3(<<"Abc">>), - - ?line <<1,2>> = encode_octet_string(<<1,2,3>>, 2), + <<_:Len/binary,Tail/binary>> = Tail0, + Res = <<Tail/binary,Bin/binary>>, + <<3,4,5,"abc">> = Res, + {'EXIT',{badarg,_}} = (catch matching_meets_construction_1(<<"Abc">>)), + {'EXIT',{badarg,_}} = (catch matching_meets_construction_2(<<"Abc">>)), + <<"Bbc">> = matching_meets_construction_3(<<"Abc">>), + + <<1,2>> = encode_octet_string(<<1,2,3>>, 2), ok. matching_meets_construction_1(<<"A",H/binary>>) -> <<"B",H>>. @@ -792,14 +801,14 @@ encode_octet_string(<<OctetString/binary>>, Len) -> <<OctetString:Len/binary-unit:8>>. simon(Config) when is_list(Config) -> - ?line one = simon(blurf, <<>>), - ?line two = simon(0, <<42>>), - ?line fc(simon, [17,<<1>>], catch simon(17, <<1>>)), - ?line fc(simon, [0,<<1,2,3>>], catch simon(0, <<1,2,3>>)), - - ?line one = simon2(blurf, <<9>>), - ?line two = simon2(0, <<9,1>>), - ?line fc(simon2, [0,<<9,10,11>>], catch simon2(0, <<9,10,11>>)), + one = simon(blurf, <<>>), + two = simon(0, <<42>>), + fc(simon, [17,<<1>>], catch simon(17, <<1>>)), + fc(simon, [0,<<1,2,3>>], catch simon(0, <<1,2,3>>)), + + one = simon2(blurf, <<9>>), + two = simon2(0, <<9,1>>), + fc(simon2, [0,<<9,10,11>>], catch simon2(0, <<9,10,11>>)), ok. simon(_, <<>>) -> one; @@ -811,10 +820,10 @@ simon2(0, <<_:16>>) -> two. %% OTP-7113: Crash in v3_codegen. matching_and_andalso(Config) when is_list(Config) -> - ?line ok = matching_and_andalso_1(<<1,2,3>>, 3), - ?line {'EXIT',{function_clause,_}} = (catch matching_and_andalso_1(<<1,2,3>>, -8)), - ?line {'EXIT',{function_clause,_}} = (catch matching_and_andalso_1(<<1,2,3>>, blurf)), - ?line {'EXIT',{function_clause,_}} = (catch matching_and_andalso_1(<<1,2,3>>, 19)), + ok = matching_and_andalso_1(<<1,2,3>>, 3), + {'EXIT',{function_clause,_}} = (catch matching_and_andalso_1(<<1,2,3>>, -8)), + {'EXIT',{function_clause,_}} = (catch matching_and_andalso_1(<<1,2,3>>, blurf)), + {'EXIT',{function_clause,_}} = (catch matching_and_andalso_1(<<1,2,3>>, 19)), {"abc",<<"xyz">>} = matching_and_andalso_2("abc", <<"-xyz">>), {"abc",<<"">>} = matching_and_andalso_2("abc", <<($a-1)>>), @@ -847,7 +856,7 @@ otp_7188(Config) when is_list(Config) -> 0,0,0,0,0,0,50,48,48,48,50,48,48,48,32,45,32,66,101,115, 116,32,79,102,32,32,32,32,32,32,32,32,32,32,32,32,32,32, 32,32,12>>, - ?line {ok,{"ID3v1", + {ok,{"ID3v1", [{title,<<68,117,154,105,232,107,121>>}, {artist,<<"Daniel Landa">>}, {album,<<"Best Of">>}]}} = parse_v1_or_v11_tag(MP3). @@ -891,11 +900,11 @@ skip_blanks_and_zero(L) -> -record(rec_otp_7233, {key, val}). otp_7233(Config) when is_list(Config) -> - ?line otp_7233_1(#rec_otp_7233{key = <<"XXabcde">>,val=[{"xxxxxxxx",42}]}), - ?line [<<"XXabcde">>,{"xxxxxxxx",42}] = get(io_format), + otp_7233_1(#rec_otp_7233{key = <<"XXabcde">>,val=[{"xxxxxxxx",42}]}), + [<<"XXabcde">>,{"xxxxxxxx",42}] = get(io_format), erase(io_format), - ?line otp_7233_1(#rec_otp_7233{key = <<"XXabcde">>,val=[]}), - ?line undefined = get(io_format), + otp_7233_1(#rec_otp_7233{key = <<"XXabcde">>,val=[]}), + undefined = get(io_format), ok. otp_7233_1(Rec) -> @@ -903,32 +912,34 @@ otp_7233_1(Rec) -> case K of <<"XX">> -> Value = Rec#rec_otp_7233.val, - case lists:keysearch("xxxxxxxx", 1, Value) of - {value,T} -> put(io_format, [Rec#rec_otp_7233.key,T]); - false -> ok + case lists:keyfind("xxxxxxxx", 1, Value) of + false -> + ok; + T -> + put(io_format, [Rec#rec_otp_7233.key,T]) end; _ -> ok end. otp_7240(Config) when is_list(Config) -> - ?line a = otp_7240_a(0, <<>>), - ?line b = otp_7240_a(1, 2), + a = otp_7240_a(0, <<>>), + b = otp_7240_a(1, 2), - ?line a = otp_7240_b(anything, <<>>), - ?line b = otp_7240_b(1, {x,y}), + a = otp_7240_b(anything, <<>>), + b = otp_7240_b(1, {x,y}), - ?line a = otp_7240_c(anything, <<>>), - ?line b = otp_7240_c(1, <<2>>), + a = otp_7240_c(anything, <<>>), + b = otp_7240_c(1, <<2>>), - ?line a = otp_7240_d(anything, <<>>), - ?line b = otp_7240_d(again, <<2>>), + a = otp_7240_d(anything, <<>>), + b = otp_7240_d(again, <<2>>), - ?line a = otp_7240_e(anything, <<>>), - ?line b = otp_7240_e(1, 41), + a = otp_7240_e(anything, <<>>), + b = otp_7240_e(1, 41), - ?line a = otp_7240_f(anything, <<>>), - ?line b = otp_7240_f(1, {}), + a = otp_7240_f(anything, <<>>), + b = otp_7240_f(1, {}), ok. @@ -951,15 +962,15 @@ otp_7240_f(_, <<>>) -> a; otp_7240_f(1, B) when is_tuple(B) -> b. otp_7498(Config) when is_list(Config) -> - ?line <<1,2,3>> = otp_7498_foo(<<1,2,3>>, 0), - ?line <<2,3>> = otp_7498_foo(<<1,2,3>>, 1), - ?line <<1,2,3>> = otp_7498_foo(<<1,2,3>>, 2), + <<1,2,3>> = otp_7498_foo(<<1,2,3>>, 0), + <<2,3>> = otp_7498_foo(<<1,2,3>>, 1), + <<1,2,3>> = otp_7498_foo(<<1,2,3>>, 2), - ?line <<1,2,3>> = otp_7498_bar(<<1,2,3>>, 0), - ?line <<2,3>> = otp_7498_bar(<<1,2,3>>, 1), - ?line <<1,2,3>> = otp_7498_bar(<<1,2,3>>, 2), - ?line <<>> = otp_7498_bar(<<>>, 2), - ?line <<1,2,3>> = otp_7498_bar(<<1,2,3>>, 3), + <<1,2,3>> = otp_7498_bar(<<1,2,3>>, 0), + <<2,3>> = otp_7498_bar(<<1,2,3>>, 1), + <<1,2,3>> = otp_7498_bar(<<1,2,3>>, 2), + <<>> = otp_7498_bar(<<>>, 2), + <<1,2,3>> = otp_7498_bar(<<1,2,3>>, 3), ok. @@ -988,19 +999,19 @@ match_string(Config) when is_list(Config) -> %% check the coverage for the v3_kernel module. case erlang:system_info(endian) of little -> - ?line do_match_string_native(<<$a,0,$b,0>>); + do_match_string_native(<<$a,0,$b,0>>); big -> - ?line do_match_string_native(<<0,$a,0,$b>>) + do_match_string_native(<<0,$a,0,$b>>) end, - ?line do_match_string_big(<<0,$a,0,$b>>), - ?line do_match_string_little(<<$a,0,$b,0>>), + do_match_string_big(<<0,$a,0,$b>>), + do_match_string_little(<<$a,0,$b,0>>), - ?line do_match_string_big_signed(<<255,255>>), - ?line do_match_string_little_signed(<<255,255>>), + do_match_string_big_signed(<<255,255>>), + do_match_string_little_signed(<<255,255>>), - ?line plain = no_match_string_opt(<<"abc">>), - ?line strange = no_match_string_opt(<<$a:9,$b:9,$c:9>>), + plain = no_match_string_opt(<<"abc">>), + strange = no_match_string_opt(<<$a:9,$b:9,$c:9>>), ok. @@ -1021,13 +1032,13 @@ no_match_string_opt(<<$a:9,$b:9,$c:9>>) -> strange. %% OTP-7591: A zero-width segment in matching would crash the compiler. zero_width(Config) when is_list(Config) -> - ?line <<Len:16/little, Str:Len/binary, 0:0>> = <<2, 0, $h, $i, 0:0>>, - ?line 2 = Len, - ?line Str = <<"hi">>, + <<Len:16/little, Str:Len/binary, 0:0>> = <<2, 0, $h, $i, 0:0>>, + 2 = Len, + Str = <<"hi">>, %% Match sure that values that cannot fit in a segment will not match. case id(<<0:8>>) of - <<256:8>> -> ?line ?t:fail(); + <<256:8>> -> ct:fail(should_not_match); _ -> ok end, ok. @@ -1036,14 +1047,14 @@ zero_width(Config) when is_list(Config) -> %% OTP_7650: A invalid size for binary segments could crash the compiler. bad_size(Config) when is_list(Config) -> Tuple = {a,b,c}, - ?line {'EXIT',{{badmatch,<<>>},_}} = (catch <<32:Tuple>> = id(<<>>)), + {'EXIT',{{badmatch,<<>>},_}} = (catch <<32:Tuple>> = id(<<>>)), Binary = <<1,2,3>>, - ?line {'EXIT',{{badmatch,<<>>},_}} = (catch <<32:Binary>> = id(<<>>)), + {'EXIT',{{badmatch,<<>>},_}} = (catch <<32:Binary>> = id(<<>>)), ok. haystack(Config) when is_list(Config) -> - ?line <<0:10/unit:8>> = haystack_1(<<0:10/unit:8>>), - ?line [<<0:10/unit:8>>, + <<0:10/unit:8>> = haystack_1(<<0:10/unit:8>>), + [<<0:10/unit:8>>, <<0:20/unit:8>>] = haystack_2(<<1:8192>>), ok. @@ -1078,10 +1089,10 @@ fc(_, Args, {'EXIT',{{case_clause,ActualArgs},_}}) %% Cover the clause handling bs_context to binary in %% beam_block:initialized_regs/2. cover_beam_bool(Config) when is_list(Config) -> - ?line ok = do_cover_beam_bool(<<>>, 3), - ?line <<19>> = do_cover_beam_bool(<<19>>, 2), - ?line <<42>> = do_cover_beam_bool(<<42>>, 1), - ?line <<17>> = do_cover_beam_bool(<<13,17>>, 0), + ok = do_cover_beam_bool(<<>>, 3), + <<19>> = do_cover_beam_bool(<<19>>, 2), + <<42>> = do_cover_beam_bool(<<42>>, 1), + <<17>> = do_cover_beam_bool(<<13,17>>, 0), ok. do_cover_beam_bool(Bin, X) when X > 0 -> @@ -1227,6 +1238,21 @@ match_string_opt(Config) when is_list(Config) -> do_match_string_opt({<<1>>,{v,V}}=T) -> {x,V,T}. +select_on_integer(Config) when is_list(Config) -> + 42 = do_select_on_integer(<<42>>), + <<"abc">> = do_select_on_integer(<<128,"abc">>), + + {'EXIT',_} = (catch do_select_on_integer(<<0:1>>)), + {'EXIT',_} = (catch do_select_on_integer(<<1:1>>)), + {'EXIT',_} = (catch do_select_on_integer(<<0:1,0:15>>)), + ok. + +%% The ASN.1 compiler frequently generates code like this. +do_select_on_integer(<<0:1,I:7>>) -> + I; +do_select_on_integer(<<1:1,_:7,Bin/binary>>) -> + Bin. + %% If 'bin_opt_info' was given the warning would lack filename %% and line number. @@ -1271,6 +1297,96 @@ do_unsafe_branch_caching(<<Code/integer, Bin/binary>>) -> _ -> Bin2 end. +bad_literals(_Config) -> + Mod = list_to_atom(?MODULE_STRING ++ "_" ++ + atom_to_list(?FUNCTION_NAME)), + S = [signed_lit_match(V, Sz) || V <- lists:seq(-8, 8), + Sz <- [0,1,2,3]] ++ + [unsigned_lit_match(V, Sz) || V <- lists:seq(-2, 8), + Sz <- [0,1,2]] ++ + [unicode_match(V) || + V <- [-100,-1,0,1,2|lists:seq(16#10FFFC, 16#110004)]], + Code = ?Q(["-module('@Mod@').\n" + "-export([f/0]).\n" + "f() ->\n" + "_@S,\n" + "ok.\n"]), + merl:print(Code), + Opts = test_lib:opt_opts(?MODULE), + {ok,_} = merl:compile_and_load(Code, Opts), + Mod:f(), + + {'EXIT',<<42>>} = (catch bad_literals_1()), + + Sz = id(8), + {'EXIT',{{badmatch,_},_}} = (catch <<-1:Sz>> = <<-1>>), + ok. + +bad_literals_1() -> + BadSz = bad, + case case <<42>> of + <<42:BadSz>> -> ok; + Val -> exit(Val) + end of + ok -> ok; + error -> error + end. + +signed_lit_match(V, Sz) -> + case <<V:Sz>> of + <<V:Sz/signed>> -> + ?Q("<<_@V@:_@Sz@/signed>> = <<_@V@:_@Sz@>>"); + _ -> + ?Q(["case <<_@V@:_@Sz@>> of\n", + " <<_@V@:_@Sz@/signed>> ->\n", + " ct:fail(should_not_match);\n", + " _ ->\n", + " ok\n", + "end\n"]) + end. + +unsigned_lit_match(V, Sz) -> + case <<V:Sz>> of + <<V:Sz/unsigned>> -> + ?Q("<<_@V@:_@Sz@>> = <<_@V@:_@Sz@>>"); + _ -> + ?Q(["case <<_@V@:_@Sz@>> of\n", + " <<_@V@:_@Sz@/unsigned>> ->\n", + " ct:fail(should_not_match);\n", + " _ ->\n", + " ok\n", + "end\n"]) + end. + +unicode_match(V) -> + try <<V/utf8>> of + <<V/utf8>> -> + ?Q(["<<_@V@/utf8>> = <<_@V@/utf8>>,\n", + "<<_@V@/utf16>> = <<_@V@/utf16>>,\n", + "<<_@V@/utf32>> = <<_@V@/utf32>>\n"]) + catch + error:badarg -> + ?Q(["case <<_@V@:32>> of\n", + " <<_@V@/utf32>> ->\n", + " ct:fail(should_not_match);\n", + " _ ->\n", + " ok\n", + "end\n"]) + end. + +%% Test a few legal but rare cases. + +good_literals(_Config) -> + Sz = id(64), + + %% Variable size. + <<42:Sz>> = id(<<42:Sz>>), + <<42.0:Sz/float>> = id(<<42:Sz/float>>), + + %% unit > 1 + <<16#cafebeef:4/unit:8>> = id(<<16#cafebeef:32>>), + ok. + check(F, R) -> R = F(). diff --git a/lib/compiler/test/bs_utf_SUITE.erl b/lib/compiler/test/bs_utf_SUITE.erl index e6d292d9e6..518e89a9cb 100644 --- a/lib/compiler/test/bs_utf_SUITE.erl +++ b/lib/compiler/test/bs_utf_SUITE.erl @@ -26,7 +26,7 @@ utf32_roundtrip/1,guard/1,extreme_tripping/1, literals/1,coverage/1]). --include_lib("test_server/include/test_server.hrl"). +-include_lib("common_test/include/ct.hrl"). suite() -> [{ct_hooks,[ts_install_cth]}]. @@ -53,14 +53,14 @@ end_per_group(_GroupName, Config) -> utf8_roundtrip(Config) when is_list(Config) -> - ?line [utf8_roundtrip_1(P) || P <- utf_data()], + [utf8_roundtrip_1(P) || P <- utf_data()], ok. utf8_roundtrip_1({Str,Bin,Bin}) -> - ?line Str = utf8_to_list(Bin), - ?line Bin = list_to_utf8(Str), - ?line [ok = utf8_guard(C, <<42,C/utf8>>) || C <- Str], - ?line [error = utf8_guard(C, <<C/utf8>>) || C <- Str], + Str = utf8_to_list(Bin), + Bin = list_to_utf8(Str), + [ok = utf8_guard(C, <<42,C/utf8>>) || C <- Str], + [error = utf8_guard(C, <<C/utf8>>) || C <- Str], ok. utf8_guard(C, Bin) when <<42,C/utf8>> =:= Bin -> ok; @@ -90,14 +90,14 @@ utf8_len(<<_/utf8,T/binary>>, N) -> utf8_len(<<>>, N) -> N. utf16_roundtrip(Config) when is_list(Config) -> - ?line {Str,Big,Big,Little,Little} = utf16_data(), - ?line 4 = utf16_big_len(Big), - ?line 4 = utf16_little_len(Little), - ?line Str = big_utf16_to_list(Big), - ?line Str = little_utf16_to_list(Little), + {Str,Big,Big,Little,Little} = utf16_data(), + 4 = utf16_big_len(Big), + 4 = utf16_little_len(Little), + Str = big_utf16_to_list(Big), + Str = little_utf16_to_list(Little), - ?line Big = list_to_big_utf16(Str), - ?line Little = list_to_little_utf16(Str), + Big = list_to_big_utf16(Str), + Little = list_to_little_utf16(Str), ok. @@ -138,14 +138,14 @@ little_utf16_to_list(<<H/little-utf16,T/binary>>) -> little_utf16_to_list(<<>>) -> []. utf32_roundtrip(Config) when is_list(Config) -> - ?line {Str,Big,Big,Little,Little} = utf32_data(), - ?line 4 = utf32_big_len(Big), - ?line 4 = utf32_little_len(Little), - ?line Str = big_utf32_to_list(Big), - ?line Str = little_utf32_to_list(Little), + {Str,Big,Big,Little,Little} = utf32_data(), + 4 = utf32_big_len(Big), + 4 = utf32_little_len(Little), + Str = big_utf32_to_list(Big), + Str = little_utf32_to_list(Little), - ?line Big = list_to_big_utf32(Str), - ?line Little = list_to_little_utf32(Str), + Big = list_to_big_utf32(Str), + Little = list_to_little_utf32(Str), ok. @@ -187,7 +187,7 @@ little_utf32_to_list(<<>>) -> []. guard(Config) when is_list(Config) -> - ?line error = do_guard(16#D800), + error = do_guard(16#D800), ok. do_guard(C) when byte_size(<<C/utf8>>) =/= 42 -> ok; @@ -199,13 +199,13 @@ do_guard(_) -> error. %% the delayed creation of sub-binaries works. extreme_tripping(Config) when is_list(Config) -> - ?line Unicode = lists:seq(0, 1024), - ?line Utf8 = unicode_to_utf8(Unicode, <<>>), - ?line Utf16 = utf8_to_utf16(Utf8, <<>>), - ?line Utf32 = utf8_to_utf32(Utf8, <<>>), - ?line Utf32 = utf16_to_utf32(Utf16, <<>>), - ?line Utf8 = utf32_to_utf8(Utf32, <<>>), - ?line Unicode = utf32_to_unicode(Utf32), + Unicode = lists:seq(0, 1024), + Utf8 = unicode_to_utf8(Unicode, <<>>), + Utf16 = utf8_to_utf16(Utf8, <<>>), + Utf32 = utf8_to_utf32(Utf8, <<>>), + Utf32 = utf16_to_utf32(Utf16, <<>>), + Utf8 = utf32_to_utf8(Utf32, <<>>), + Unicode = utf32_to_unicode(Utf32), ok. unicode_to_utf8([C|T], Bin) -> @@ -233,58 +233,58 @@ utf32_to_unicode(<<C/utf32,T/binary>>) -> utf32_to_unicode(<<>>) -> []. literals(Config) when is_list(Config) -> - ?line abc_utf8 = match_literal(<<"abc"/utf8>>), - ?line abc_utf8 = match_literal(<<$a,$b,$c>>), - - ?line abc_utf16be = match_literal(<<"abc"/utf16>>), - ?line abc_utf16be = match_literal(<<$a:16,$b:16,$c:16>>), - ?line abc_utf16le = match_literal(<<"abc"/little-utf16>>), - ?line abc_utf16le = match_literal(<<$a:16/little,$b:16/little,$c:16/little>>), - - ?line abc_utf32be = match_literal(<<"abc"/utf32>>), - ?line abc_utf32be = match_literal(<<$a:32,$b:32,$c:32>>), - ?line abc_utf32le = match_literal(<<"abc"/little-utf32>>), - ?line abc_utf32le = match_literal(<<$a:32/little,$b:32/little,$c:32/little>>), - - ?line bjorn_utf8 = match_literal(<<"bj\366rn"/utf8>>), - ?line bjorn_utf8 = match_literal(<<$b,$j,195,182,$r,$n>>), - - ?line bjorn_utf16be = match_literal(<<"bj\366rn"/utf16>>), - ?line bjorn_utf16be = match_literal(<<$b:16,$j:16,246:16,$r:16,$n:16>>), - ?line bjorn_utf16le = match_literal(<<"bj\366rn"/little-utf16>>), - ?line bjorn_utf16le = match_literal(<<$b:16/little,$j:16/little, + abc_utf8 = match_literal(<<"abc"/utf8>>), + abc_utf8 = match_literal(<<$a,$b,$c>>), + + abc_utf16be = match_literal(<<"abc"/utf16>>), + abc_utf16be = match_literal(<<$a:16,$b:16,$c:16>>), + abc_utf16le = match_literal(<<"abc"/little-utf16>>), + abc_utf16le = match_literal(<<$a:16/little,$b:16/little,$c:16/little>>), + + abc_utf32be = match_literal(<<"abc"/utf32>>), + abc_utf32be = match_literal(<<$a:32,$b:32,$c:32>>), + abc_utf32le = match_literal(<<"abc"/little-utf32>>), + abc_utf32le = match_literal(<<$a:32/little,$b:32/little,$c:32/little>>), + + bjorn_utf8 = match_literal(<<"bj\366rn"/utf8>>), + bjorn_utf8 = match_literal(<<$b,$j,195,182,$r,$n>>), + + bjorn_utf16be = match_literal(<<"bj\366rn"/utf16>>), + bjorn_utf16be = match_literal(<<$b:16,$j:16,246:16,$r:16,$n:16>>), + bjorn_utf16le = match_literal(<<"bj\366rn"/little-utf16>>), + bjorn_utf16le = match_literal(<<$b:16/little,$j:16/little, 246:16/little,$r:16/little, $n:16/little>>), - ?line <<244,143,191,191>> = <<16#10ffff/utf8>>, + <<244,143,191,191>> = <<16#10ffff/utf8>>, %% Invalid literals. I = 0, - ?line {'EXIT',{badarg,_}} = (catch <<(-1)/utf8,I/utf8>>), - ?line {'EXIT',{badarg,_}} = (catch <<(-1)/utf16,I/utf8>>), - ?line {'EXIT',{badarg,_}} = (catch <<(-1)/little-utf16,I/utf8>>), - ?line {'EXIT',{badarg,_}} = (catch <<(-1)/utf32,I/utf8>>), - ?line {'EXIT',{badarg,_}} = (catch <<(-1)/little-utf32,I/utf8>>), - ?line {'EXIT',{badarg,_}} = (catch <<16#D800/utf8,I/utf8>>), - ?line {'EXIT',{badarg,_}} = (catch <<16#D800/utf16,I/utf8>>), - ?line {'EXIT',{badarg,_}} = (catch <<16#D800/little-utf16,I/utf8>>), - ?line {'EXIT',{badarg,_}} = (catch <<16#D800/utf32,I/utf8>>), - ?line {'EXIT',{badarg,_}} = (catch <<16#D800/little-utf32,I/utf8>>), + {'EXIT',{badarg,_}} = (catch <<(-1)/utf8,I/utf8>>), + {'EXIT',{badarg,_}} = (catch <<(-1)/utf16,I/utf8>>), + {'EXIT',{badarg,_}} = (catch <<(-1)/little-utf16,I/utf8>>), + {'EXIT',{badarg,_}} = (catch <<(-1)/utf32,I/utf8>>), + {'EXIT',{badarg,_}} = (catch <<(-1)/little-utf32,I/utf8>>), + {'EXIT',{badarg,_}} = (catch <<16#D800/utf8,I/utf8>>), + {'EXIT',{badarg,_}} = (catch <<16#D800/utf16,I/utf8>>), + {'EXIT',{badarg,_}} = (catch <<16#D800/little-utf16,I/utf8>>), + {'EXIT',{badarg,_}} = (catch <<16#D800/utf32,I/utf8>>), + {'EXIT',{badarg,_}} = (catch <<16#D800/little-utf32,I/utf8>>), B = 16#10FFFF+1, - ?line {'EXIT',{badarg,_}} = (catch <<B/utf8>>), - ?line {'EXIT',{badarg,_}} = (catch <<B/utf16>>), - ?line {'EXIT',{badarg,_}} = (catch <<B/little-utf16>>), - ?line {'EXIT',{badarg,_}} = (catch <<B/utf32>>), - ?line {'EXIT',{badarg,_}} = (catch <<B/little-utf32>>), + {'EXIT',{badarg,_}} = (catch <<B/utf8>>), + {'EXIT',{badarg,_}} = (catch <<B/utf16>>), + {'EXIT',{badarg,_}} = (catch <<B/little-utf16>>), + {'EXIT',{badarg,_}} = (catch <<B/utf32>>), + {'EXIT',{badarg,_}} = (catch <<B/little-utf32>>), %% Matching of bad literals. - ?line error = bad_literal_match(<<237,160,128>>), %16#D800 in UTF-8 - ?line error = bad_literal_match(<<244,144,128,128>>), %16#110000 in UTF-8 + error = bad_literal_match(<<237,160,128>>), %16#D800 in UTF-8 + error = bad_literal_match(<<244,144,128,128>>), %16#110000 in UTF-8 - ?line error = bad_literal_match(<<16#D800:32>>), - ?line error = bad_literal_match(<<16#110000:32>>), - ?line error = bad_literal_match(<<16#D800:32/little>>), - ?line error = bad_literal_match(<<16#110000:32/little>>), + error = bad_literal_match(<<16#D800:32>>), + error = bad_literal_match(<<16#110000:32>>), + error = bad_literal_match(<<16#D800:32/little>>), + error = bad_literal_match(<<16#110000:32/little>>), ok. @@ -307,13 +307,13 @@ bad_literal_match(_) -> error. coverage(Config) when is_list(Config) -> %% Cover bit syntax matching optimizations in v3_kernel. - ?line 0 = coverage_1(<<4096/utf8,65536/utf8,0>>), - ?line 1 = coverage_1(<<4096/utf8,65536/utf8,1>>), + 0 = coverage_1(<<4096/utf8,65536/utf8,0>>), + 1 = coverage_1(<<4096/utf8,65536/utf8,1>>), - ?line 0 = coverage_2(<<4096/utf8,65536/utf8,0>>), - ?line 1 = coverage_2(<<1024/utf8,1025/utf8,1>>), + 0 = coverage_2(<<4096/utf8,65536/utf8,0>>), + 1 = coverage_2(<<1024/utf8,1025/utf8,1>>), - ?line fc(catch coverage_3(1)), + fc(catch coverage_3(1)), %% Cover beam_flatten (combining the heap allocation in %% a subsequent test_heap instruction into the bs_init2 diff --git a/lib/compiler/test/compilation_SUITE.erl b/lib/compiler/test/compilation_SUITE.erl index 2715a3aec5..76b7e852f1 100644 --- a/lib/compiler/test/compilation_SUITE.erl +++ b/lib/compiler/test/compilation_SUITE.erl @@ -20,11 +20,13 @@ -module(compilation_SUITE). --include_lib("test_server/include/test_server.hrl"). +-include_lib("common_test/include/ct.hrl"). -compile(export_all). -suite() -> [{ct_hooks,[ts_install_cth]}]. +suite() -> + [{ct_hooks,[ts_install_cth]}, + {timetrap,{minutes,10}}]. all() -> test_lib:recompile(?MODULE), @@ -164,11 +166,9 @@ split({int, N}, <<N:16,B:N/binary,T/binary>>) -> ?comp(on_load). ?comp(on_load_inline). -beam_compiler_7(doc) -> - "Code snippet submitted from Ulf Wiger which fails in R3 Beam."; -beam_compiler_7(suite) -> []; +%% Code snippet submitted from Ulf Wiger which fails in R3 Beam. beam_compiler_7(Config) when is_list(Config) -> - ?line done = empty(2, false). + done = empty(2, false). empty(N, Toggle) when N > 0 -> %% R3 Beam copies the second argument to the first before call. @@ -194,16 +194,17 @@ redundant_case_1(4) -> d; redundant_case_1(_) -> d. failure(Module, Conf) -> - ?line Src = filename:join(?config(data_dir, Conf), atom_to_list(Module)), - ?line Out = ?config(priv_dir,Conf), - ?line io:format("Compiling: ~ts\n", [Src]), - ?line CompRc = compile:file(Src, [{outdir,Out},return,time]), - ?line io:format("Result: ~p\n",[CompRc]), - ?line case CompRc of - error -> ok; - {error,Errors,_} -> check_errors(Errors); - _ -> test_server:fail({no_error, CompRc}) - end, + Src = filename:join(proplists:get_value(data_dir, Conf), + atom_to_list(Module)), + Out = proplists:get_value(priv_dir, Conf), + io:format("Compiling: ~ts\n", [Src]), + CompRc = compile:file(Src, [{outdir,Out},return,time]), + io:format("Result: ~p\n",[CompRc]), + case CompRc of + error -> ok; + {error,Errors,_} -> check_errors(Errors); + _ -> ct:fail({no_error, CompRc}) + end, ok. check_errors([{_,Eds}|T]) -> @@ -224,7 +225,7 @@ check_error_1(Str0) -> io:format("~s\n", [Str]), case Str of "internal"++_=Str -> - ?t:fail(internal_compiler_error); + ct:fail(internal_compiler_error); _ -> ok end. @@ -234,51 +235,51 @@ check_error_1(Str0) -> try_it(Module, Conf) -> %% Change 'false' to 'true' to start a new node for every module. try_it(false, Module, Conf). - + try_it(StartNode, Module, Conf) -> - ?line OtherOpts = [], %Can be changed to [time] if needed - ?line Src = filename:join(?config(data_dir, Conf), atom_to_list(Module)), - ?line Out = ?config(priv_dir,Conf), - ?line io:format("Compiling: ~s\n", [Src]), - ?line CompRc0 = compile:file(Src, [clint,{outdir,Out},report, + try_it(StartNode, Module, {minutes,10}, Conf). + +try_it(StartNode, Module, Timetrap, Conf) -> + OtherOpts = [], %Can be changed to [time] if needed + Src = filename:join(proplists:get_value(data_dir, Conf), + atom_to_list(Module)), + Out = proplists:get_value(priv_dir,Conf), + io:format("Compiling: ~s\n", [Src]), + CompRc0 = compile:file(Src, [clint,{outdir,Out},report, bin_opt_info|OtherOpts]), - ?line io:format("Result: ~p\n",[CompRc0]), - ?line {ok,_Mod} = CompRc0, + io:format("Result: ~p\n",[CompRc0]), + {ok,_Mod} = CompRc0, - ?line Dog = test_server:timetrap(test_server:minutes(10)), Node = case StartNode of false -> node(); true -> - ?line Pa = "-pa " ++ filename:dirname(code:which(?MODULE)), - ?line {ok,Node0} = start_node(compiler, Pa), + Pa = "-pa " ++ filename:dirname(code:which(?MODULE)), + {ok,Node0} = start_node(compiler, Pa), Node0 end, - ?line ok = rpc:call(Node, ?MODULE, load_and_call, [Out, Module]), - ?line load_and_call(Out, Module), - ?line test_server:timetrap_cancel(Dog), + ok = rpc:call(Node, ?MODULE, load_and_call, [Out, Module]), + load_and_call(Out, Module), - ?line NewDog = test_server:timetrap(test_server:minutes(10)), - ?line io:format("Compiling (without optimization): ~s\n", [Src]), - ?line CompRc1 = compile:file(Src, + ct:timetrap(Timetrap), + io:format("Compiling (without optimization): ~s\n", [Src]), + CompRc1 = compile:file(Src, [no_copt,no_postopt,{outdir,Out},report|OtherOpts]), - ?line io:format("Result: ~p\n",[CompRc1]), - ?line {ok,_Mod} = CompRc1, - ?line ok = rpc:call(Node, ?MODULE, load_and_call, [Out, Module]), - ?line test_server:timetrap_cancel(NewDog), + io:format("Result: ~p\n",[CompRc1]), + {ok,_Mod} = CompRc1, + ok = rpc:call(Node, ?MODULE, load_and_call, [Out, Module]), - ?line LastDog = test_server:timetrap(test_server:minutes(10)), - ?line io:format("Compiling (with old inliner): ~s\n", [Src]), - ?line CompRc2 = compile:file(Src, [{outdir,Out},report,bin_opt_info, + ct:timetrap(Timetrap), + io:format("Compiling (with old inliner): ~s\n", [Src]), + CompRc2 = compile:file(Src, [{outdir,Out},report,bin_opt_info, {inline,1000}|OtherOpts]), - ?line io:format("Result: ~p\n",[CompRc2]), - ?line {ok,_Mod} = CompRc2, - ?line ok = rpc:call(Node, ?MODULE, load_and_call, [Out, Module]), - ?line test_server:timetrap_cancel(LastDog), + io:format("Result: ~p\n",[CompRc2]), + {ok,_Mod} = CompRc2, + ok = rpc:call(Node, ?MODULE, load_and_call, [Out, Module]), - AsmDog = test_server:timetrap(test_server:minutes(10)), + ct:timetrap(Timetrap), io:format("Compiling (from assembly): ~s\n", [Src]), {ok,_} = compile:file(Src, [to_asm,{outdir,Out},report|OtherOpts]), Asm = filename:join(Out, lists:concat([Module, ".S"])), @@ -286,28 +287,26 @@ try_it(StartNode, Module, Conf) -> io:format("Result: ~p\n",[CompRc3]), {ok,_} = CompRc3, ok = rpc:call(Node, ?MODULE, load_and_call, [Out, Module]), - test_server:timetrap_cancel(AsmDog), case StartNode of false -> ok; - true -> ?line test_server:stop_node(Node) + true -> test_server:stop_node(Node) end, - ?line test_server:timetrap_cancel(LastDog), ok. load_and_call(Out, Module) -> - ?line io:format("Loading...\n",[]), - ?line {module,Module} = code:load_abs(filename:join(Out, Module)), + io:format("Loading...\n",[]), + {module,Module} = code:load_abs(filename:join(Out, Module)), - ?line io:format("Calling...\n",[]), + io:format("Calling...\n",[]), %% Call M:M, and expect ok back, that's our interface - ?line CallRc = Module:Module(), - ?line io:format("Got value: ~p\n",[CallRc]), + CallRc = Module:Module(), + io:format("Got value: ~p\n",[CallRc]), - ?line ok = CallRc, + ok = CallRc, %% Smoke-test of beam disassembler. - ?line test_lib:smoke_disasm(Module), + test_lib:smoke_disasm(Module), _ = code:delete(Module), _ = code:purge(Module), @@ -330,7 +329,7 @@ start_node(Name, Args) -> {ok, Node} -> {ok, Node}; Error -> - ?line test_server:fail(Error) + ct:fail(Error) end. from(H, [H | T]) -> T; @@ -338,84 +337,78 @@ from(H, [_ | T]) -> from(H, T); from(_, []) -> []. -vsn_1(doc) -> - "Test generation of 'vsn' attribute"; -vsn_1(suite) -> []; +%% Test generation of 'vsn' attribute. vsn_1(Conf) when is_list(Conf) -> - ?line M = vsn_1, - - ?line compile_load(M, ?config(data_dir, Conf), Conf), - ?line Vsn1 = get_vsn(M), - ?line timer:sleep(1000), - - ?line compile_load(M, ?config(data_dir, Conf), Conf), - ?line Vsn2 = get_vsn(M), - - ?line compile_load(M, filename:join(?config(data_dir, Conf), "other"), - Conf), - ?line Vsn3 = get_vsn(M), - ?line if - Vsn1 == Vsn2, Vsn2 == Vsn3 -> - ok; - true -> - test_server:fail({vsn, Vsn1, Vsn2, Vsn3}) - end, + M = vsn_1, + + compile_load(M, proplists:get_value(data_dir, Conf), Conf), + Vsn1 = get_vsn(M), + timer:sleep(1000), + + compile_load(M, proplists:get_value(data_dir, Conf), Conf), + Vsn2 = get_vsn(M), + + compile_load(M, filename:join(proplists:get_value(data_dir, Conf), + "other"), + Conf), + Vsn3 = get_vsn(M), + if + Vsn1 == Vsn2, Vsn2 == Vsn3 -> + ok; + true -> + ct:fail({vsn, Vsn1, Vsn2, Vsn3}) + end, ok. -vsn_2(doc) -> - "Test overriding of generation of 'vsn' attribute"; -vsn_2(suite) -> []; +%% Test overriding of generation of 'vsn' attribute. vsn_2(Conf) when is_list(Conf) -> - ?line M = vsn_2, - - ?line compile_load(M, ?config(data_dir, Conf), Conf), - ?line Vsn = get_vsn(M), - ?line case Vsn of - [34] -> - ok; - _ -> - test_server:fail({vsn, Vsn}) - end, + M = vsn_2, + + compile_load(M, proplists:get_value(data_dir, Conf), Conf), + Vsn = get_vsn(M), + case Vsn of + [34] -> + ok; + _ -> + ct:fail({vsn, Vsn}) + end, ok. -vsn_3(doc) -> - "Test that different code yields different generated 'vsn'"; -vsn_3(suite) -> []; +%% Test that different code yields different generated 'vsn'. vsn_3(Conf) when is_list(Conf) -> - ?line M = vsn_3, - - ?line compile_load(M, ?config(data_dir, Conf), Conf), - ?line Vsn1 = get_vsn(M), - - ?line compile_load(M, filename:join(?config(data_dir, Conf), "other"), - Conf), - ?line Vsn2 = get_vsn(M), - ?line if - Vsn1 /= Vsn2 -> - ok; - true -> - test_server:fail({vsn, Vsn1, Vsn2}) - end, + M = vsn_3, + + compile_load(M, proplists:get_value(data_dir, Conf), Conf), + Vsn1 = get_vsn(M), + + compile_load(M, filename:join(proplists:get_value(data_dir, Conf), + "other"), + Conf), + Vsn2 = get_vsn(M), + if + Vsn1 /= Vsn2 -> + ok; + true -> + ct:fail({vsn, Vsn1, Vsn2}) + end, ok. get_vsn(M) -> - {value, {vsn, V}} = lists:keysearch(vsn, 1, M:module_info(attributes)), + {vsn,V} = lists:keyfind(vsn, 1, M:module_info(attributes)), V. long_string(Config) when is_list(Config) -> %% The test must complete in one minute - it should be plenty of time. - ?line Dog = test_server:timetrap(test_server:minutes(1)), - ?line try_it(long_string, Config), - ?line test_server:timetrap_cancel(Dog), + try_it(false, long_string, {minutes,1}, Config), ok. compile_load(Module, Dir, Conf) -> - ?line Src = filename:join(Dir, atom_to_list(Module)), - ?line Out = ?config(priv_dir,Conf), - ?line CompRc = compile:file(Src, [{outdir,Out}]), - ?line {ok, Module} = CompRc, - ?line code:purge(Module), - ?line {module, Module} = + Src = filename:join(Dir, atom_to_list(Module)), + Out = proplists:get_value(priv_dir,Conf), + CompRc = compile:file(Src, [{outdir,Out}]), + {ok, Module} = CompRc, + code:purge(Module), + {module, Module} = code:load_abs(filename:join(Out, atom_to_list(Module))), ok. @@ -428,9 +421,9 @@ self_compile_old_inliner(Config) when is_list(Config) -> self_compile_1(Config, "old", [verbose,{inline,500}]). self_compile_1(Config, Prefix, Opts) -> - Dog = test_server:timetrap(test_server:minutes(40)), + ct:timetrap({minutes,40}), - Priv = ?config(priv_dir,Config), + Priv = proplists:get_value(priv_dir,Config), Version = compiler_version(), %% Compile the compiler. (In this node to get better coverage.) @@ -449,11 +442,10 @@ self_compile_1(Config, Prefix, Opts) -> %% be equal (except for beam_asm that contains the compiler version). compare_compilers(CompA, CompB), - test_server:timetrap_cancel(Dog), ok. self_compile_node(CompilerDir, OutDir, Version, Opts) -> - Dog = test_server:timetrap(test_server:minutes(15)), + ct:timetrap({minutes,15}), Pa = "-pa " ++ filename:dirname(code:which(?MODULE)) ++ " -pa " ++ CompilerDir, Files = compiler_src(), @@ -462,11 +454,11 @@ self_compile_node(CompilerDir, OutDir, Version, Opts) -> %% because it will load the same cover-compiled code as on this %% node. Use a shielded node to prevent the cover server from %% being started. - ?t:run_on_shielded_node( - fun() -> - compile_compiler(Files, OutDir, Version, Opts) - end, Pa), - test_server:timetrap_cancel(Dog), + test_server:run_on_shielded_node( + fun() -> + compile_compiler(Files, OutDir, Version, Opts) + end, Pa), + ok. compile_compiler(Files, OutDir, Version, InlineOpts) -> @@ -619,11 +611,11 @@ otp_7345(ObjRef, _RdEnv, Args) -> %% Check the generation of the string table. string_table(Config) when is_list(Config) -> - ?line DataDir = ?config(data_dir, Config), - ?line File = filename:join(DataDir, "string_table.erl"), - ?line {ok,string_table,Beam,[]} = compile:file(File, [return, binary]), - ?line {ok,{string_table,[StringTableChunk]}} = beam_lib:chunks(Beam, ["StrT"]), - ?line {"StrT", <<"stringtable">>} = StringTableChunk, + DataDir = proplists:get_value(data_dir, Config), + File = filename:join(DataDir, "string_table.erl"), + {ok,string_table,Beam,[]} = compile:file(File, [return, binary]), + {ok,{string_table,[StringTableChunk]}} = beam_lib:chunks(Beam, ["StrT"]), + {"StrT", <<"stringtable">>} = StringTableChunk, ok. otp_8949_a(Config) when is_list(Config) -> @@ -650,8 +642,8 @@ do_otp_8949_a() -> otp_8949_b(Config) when is_list(Config) -> self() ! something, - ?line value = otp_8949_b([], false), - ?line {'EXIT',_} = (catch otp_8949_b([], true)), + value = otp_8949_b([], false), + {'EXIT',_} = (catch otp_8949_b([], true)), ok. %% Would cause an endless loop in beam_utils. diff --git a/lib/compiler/test/compile_SUITE.erl b/lib/compiler/test/compile_SUITE.erl index cbdd9ce8cd..b2e9558cba 100644 --- a/lib/compiler/test/compile_SUITE.erl +++ b/lib/compiler/test/compile_SUITE.erl @@ -21,7 +21,7 @@ %% Tests compile:file/1 and compile:file/2 with various options. --include_lib("test_server/include/test_server.hrl"). +-include_lib("common_test/include/ct.hrl"). -export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, init_per_group/2,end_per_group/2, @@ -29,7 +29,7 @@ file_1/1, forms_2/1, module_mismatch/1, big_file/1, outdir/1, binary/1, makedep/1, cond_and_ifdef/1, listings/1, listings_big/1, other_output/1, encrypted_abstr/1, - bad_record_use1/1, bad_record_use2/1, strict_record/1, + strict_record/1, missing_testheap/1, cover/1, env/1, core/1, asm/1, sys_pre_attributes/1, dialyzer/1, warnings/1 @@ -48,13 +48,12 @@ all() -> [app_test, appup_test, file_1, forms_2, module_mismatch, big_file, outdir, binary, makedep, cond_and_ifdef, listings, listings_big, other_output, encrypted_abstr, - {group, bad_record_use}, strict_record, + strict_record, missing_testheap, cover, env, core, asm, sys_pre_attributes, dialyzer, warnings]. groups() -> - [{bad_record_use, [], - [bad_record_use1, bad_record_use2]}]. + []. init_per_suite(Config) -> Config. @@ -72,58 +71,55 @@ end_per_group(_GroupName, Config) -> %% Test that the Application file has no `basic' errors."; app_test(Config) when is_list(Config) -> - ?line ?t:app_test(compiler). + test_server:app_test(compiler). %% Test that the Application upgrade file has no `basic' errors."; appup_test(Config) when is_list(Config) -> - ok = ?t:appup_test(compiler). + ok = test_server:appup_test(compiler). %% Tests that we can compile and run a simple Erlang program, %% using compile:file/1. file_1(Config) when is_list(Config) -> - ?line Dog = test_server:timetrap(test_server:minutes(5)), - process_flag(trap_exit, true), - ?line {Simple, Target} = files(Config, "file_1"), - ?line {ok, Cwd} = file:get_cwd(), - ?line ok = file:set_cwd(filename:dirname(Target)), + {Simple, Target} = get_files(Config, simple, "file_1"), + {ok, Cwd} = file:get_cwd(), + ok = file:set_cwd(filename:dirname(Target)), %% Native from BEAM without compilation info. - ?line {ok,simple} = compile:file(Simple, [slim]), %Smoke test only. - ?line {ok,simple} = compile:file(Target, [native,from_beam]), %Smoke test. + {ok,simple} = compile:file(Simple, [slim]), %Smoke test only. + {ok,simple} = compile:file(Target, [native,from_beam]), %Smoke test. %% Native from BEAM with compilation info. - ?line {ok,simple} = compile:file(Simple), %Smoke test only. - ?line {ok,simple} = compile:file(Target, [native,from_beam]), %Smoke test. + {ok,simple} = compile:file(Simple), %Smoke test only. + {ok,simple} = compile:file(Target, [native,from_beam]), %Smoke test. - ?line {ok,simple} = compile:file(Simple, [native,report]), %Smoke test. + {ok,simple} = compile:file(Simple, [native,report]), %Smoke test. - ?line compile_and_verify(Simple, Target, []), - ?line compile_and_verify(Simple, Target, [native]), - ?line compile_and_verify(Simple, Target, [debug_info]), - ?line {ok,simple} = compile:file(Simple, [no_line_info]), %Coverage + compile_and_verify(Simple, Target, []), + compile_and_verify(Simple, Target, [native]), + compile_and_verify(Simple, Target, [debug_info]), + {ok,simple} = compile:file(Simple, [no_line_info]), %Coverage {ok,simple} = compile:file(Simple, [{eprof,beam_z}]), %Coverage - ?line ok = file:set_cwd(Cwd), - ?line true = exists(Target), - ?line passed = run(Target, test, []), + ok = file:set_cwd(Cwd), + true = exists(Target), + passed = run(Target, test, []), %% Cleanup. - ?line ok = file:delete(Target), - ?line ok = file:del_dir(filename:dirname(Target)), + ok = file:delete(Target), + ok = file:del_dir(filename:dirname(Target)), %% There should not be any messages in the messages. receive Any -> - ?t:fail({unexpected,Any}) + ct:fail({unexpected,Any}) after 10 -> ok end, - ?line test_server:timetrap_cancel(Dog), ok. forms_2(Config) when is_list(Config) -> @@ -147,121 +143,110 @@ forms_2(Config) when is_list(Config) -> ok. module_mismatch(Config) when is_list(Config) -> - ?line DataDir = ?config(data_dir, Config), - ?line File = filename:join(DataDir, "wrong_module_name.erl"), + DataDir = proplists:get_value(data_dir, Config), + File = filename:join(DataDir, "wrong_module_name.erl"), {error,[{"wrong_module_name.beam", [{none,compile,{module_name,arne,"wrong_module_name"}}]}], []} = compile:file(File, [return]), - ?line error = compile:file(File, [report]), + error = compile:file(File, [report]), - ?line {ok,arne,[]} = compile:file(File, + {ok,arne,[]} = compile:file(File, [return,no_error_module_mismatch]), ok. big_file(Config) when is_list(Config) -> - ?line Dog = test_server:timetrap(test_server:minutes(5)), - ?line DataDir = ?config(data_dir, Config), - ?line PrivDir = ?config(priv_dir, Config), - ?line Big = filename:join(DataDir, "big.erl"), - ?line Target = filename:join(PrivDir, "big.beam"), - ?line ok = file:set_cwd(PrivDir), - ?line compile_and_verify(Big, Target, []), - ?line compile_and_verify(Big, Target, [debug_info]), - ?line compile_and_verify(Big, Target, [no_postopt]), + {Big,Target} = get_files(Config, big, "big_file"), + ok = file:set_cwd(filename:dirname(Target)), + compile_and_verify(Big, Target, []), + compile_and_verify(Big, Target, [debug_info]), + compile_and_verify(Big, Target, [no_postopt]), %% Cleanup. - ?line ok = file:delete(Target), - ?line test_server:timetrap_cancel(Dog), + ok = file:delete(Target), ok. %% Tests that the {outdir, Dir} option works. outdir(Config) when is_list(Config) -> - ?line Dog = test_server:timetrap(test_server:seconds(60)), - ?line {Simple, Target} = files(Config, "outdir"), - ?line {ok, simple} = compile:file(Simple, [{outdir, filename:dirname(Target)}]), - ?line true = exists(Target), - ?line passed = run(Target, test, []), - ?line ok = file:delete(Target), - ?line ok = file:del_dir(filename:dirname(Target)), - ?line test_server:timetrap_cancel(Dog), + {Simple, Target} = get_files(Config, simple, "outdir"), + {ok, simple} = compile:file(Simple, [{outdir, filename:dirname(Target)}]), + true = exists(Target), + passed = run(Target, test, []), + ok = file:delete(Target), + ok = file:del_dir(filename:dirname(Target)), ok. %% Tests that the binary option works. binary(Config) when is_list(Config) -> - ?line Dog = test_server:timetrap(test_server:seconds(60)), - ?line {Simple, Target} = files(Config, "binary"), - ?line {ok, simple, Binary} = compile:file(Simple, [binary]), - ?line code:load_binary(simple, Target, Binary), - ?line passed = simple:test(), - ?line true = code:delete(simple), - ?line false = code:purge(simple), - ?line ok = file:del_dir(filename:dirname(Target)), - ?line test_server:timetrap_cancel(Dog), + {Simple, Target} = get_files(Config, simple, "binary"), + {ok, simple, Binary} = compile:file(Simple, [binary]), + code:load_binary(simple, Target, Binary), + passed = simple:test(), + true = code:delete(simple), + false = code:purge(simple), + ok = file:del_dir(filename:dirname(Target)), ok. %% Tests that the dependencies-Makefile-related options work. makedep(Config) when is_list(Config) -> - ?line Dog = test_server:timetrap(test_server:seconds(60)), - ?line {Simple,Target} = files(Config, "makedep"), - ?line DataDir = ?config(data_dir, Config), - ?line SimpleRootname = filename:rootname(Simple), - ?line IncludeDir = filename:join(filename:dirname(Simple), "include"), - ?line IncludeOptions = [ - {d,need_foo}, - {d,foo_value,42}, - {d,include_generated}, - {i,IncludeDir} - ], + {Simple,Target} = get_files(Config, simple, "makedep"), + DataDir = proplists:get_value(data_dir, Config), + SimpleRootname = filename:rootname(Simple), + IncludeDir = filename:join(filename:dirname(Simple), "include"), + IncludeOptions = [ + {d,need_foo}, + {d,foo_value,42}, + {d,include_generated}, + {i,IncludeDir} + ], %% Basic rule. - ?line BasicMf1Name = SimpleRootname ++ "-basic1.mk", - ?line {ok,BasicMf1} = file:read_file(BasicMf1Name), - ?line {ok,_,Mf1} = compile:file(Simple, [binary,makedep]), - ?line BasicMf1 = makedep_canonicalize_result(Mf1, DataDir), + BasicMf1Name = SimpleRootname ++ "-basic1.mk", + {ok,BasicMf1} = file:read_file(BasicMf1Name), + {ok,_,Mf1} = compile:file(Simple, [binary,makedep]), + BasicMf1 = makedep_canonicalize_result(Mf1, DataDir), %% Basic rule with one existing header. - ?line BasicMf2Name = SimpleRootname ++ "-basic2.mk", - ?line {ok,BasicMf2} = file:read_file(BasicMf2Name), - ?line {ok,_,Mf2} = compile:file(Simple, [binary,makedep|IncludeOptions]), - ?line BasicMf2 = makedep_canonicalize_result(Mf2, DataDir), + BasicMf2Name = SimpleRootname ++ "-basic2.mk", + {ok,BasicMf2} = file:read_file(BasicMf2Name), + {ok,_,Mf2} = compile:file(Simple, [binary,makedep|IncludeOptions]), + BasicMf2 = makedep_canonicalize_result(Mf2, DataDir), %% Rule with one existing header and one missing header. - ?line MissingMfName = SimpleRootname ++ "-missing.mk", - ?line {ok,MissingMf} = file:read_file(MissingMfName), - ?line {ok,_,Mf3} = compile:file(Simple, + MissingMfName = SimpleRootname ++ "-missing.mk", + {ok,MissingMf} = file:read_file(MissingMfName), + {ok,_,Mf3} = compile:file(Simple, [binary,makedep,makedep_add_missing|IncludeOptions]), - ?line MissingMf = makedep_canonicalize_result(Mf3, DataDir), + MissingMf = makedep_canonicalize_result(Mf3, DataDir), %% Rule with modified target. - ?line TargetMf1Name = SimpleRootname ++ "-target1.mk", - ?line {ok,TargetMf1} = file:read_file(TargetMf1Name), - ?line {ok,_,Mf4} = compile:file(Simple, + TargetMf1Name = SimpleRootname ++ "-target1.mk", + {ok,TargetMf1} = file:read_file(TargetMf1Name), + {ok,_,Mf4} = compile:file(Simple, [binary,makedep,{makedep_target,"$target"}|IncludeOptions]), - ?line TargetMf1 = makedep_modify_target( + TargetMf1 = makedep_modify_target( makedep_canonicalize_result(Mf4, DataDir), "$$target"), %% Rule with quoted modified target. - ?line TargetMf2Name = SimpleRootname ++ "-target2.mk", - ?line {ok,TargetMf2} = file:read_file(TargetMf2Name), - ?line {ok,_,Mf5} = compile:file(Simple, + TargetMf2Name = SimpleRootname ++ "-target2.mk", + {ok,TargetMf2} = file:read_file(TargetMf2Name), + {ok,_,Mf5} = compile:file(Simple, [binary,makedep,{makedep_target,"$target"},makedep_quote_target| IncludeOptions]), - ?line TargetMf2 = makedep_modify_target( + TargetMf2 = makedep_modify_target( makedep_canonicalize_result(Mf5, DataDir), "$$target"), %% Basic rule written to some file. - ?line {ok,_} = compile:file(Simple, + {ok,_} = compile:file(Simple, [makedep,{makedep_output,Target}|IncludeOptions]), - ?line {ok,Mf6} = file:read_file(Target), - ?line BasicMf2 = makedep_canonicalize_result(Mf6, DataDir), + {ok,Mf6} = file:read_file(Target), + BasicMf2 = makedep_canonicalize_result(Mf6, DataDir), %% Rule with creating phony target. - ?line PhonyMfName = SimpleRootname ++ "-phony.mk", - ?line {ok,PhonyMf} = file:read_file(PhonyMfName), - ?line {ok,_,Mf7} = compile:file(Simple, + PhonyMfName = SimpleRootname ++ "-phony.mk", + {ok,PhonyMf} = file:read_file(PhonyMfName), + {ok,_,Mf7} = compile:file(Simple, [binary,makedep,makedep_phony|IncludeOptions]), - ?line PhonyMf = makedep_canonicalize_result(Mf7, DataDir), + PhonyMf = makedep_canonicalize_result(Mf7, DataDir), - ?line ok = file:delete(Target), - ?line ok = file:del_dir(filename:dirname(Target)), - ?line test_server:timetrap_cancel(Dog), + ok = file:delete(Target), + ok = file:del_dir(filename:dirname(Target)), ok. makedep_canonicalize_result(Mf, DataDir) -> @@ -281,30 +266,26 @@ makedep_modify_target(Mf, Target) -> %% Tests that conditional compilation, defining values, including files work. cond_and_ifdef(Config) when is_list(Config) -> - ?line Dog = test_server:timetrap(test_server:seconds(60)), - ?line {Simple, Target} = files(Config, "cond_and_ifdef"), - ?line IncludeDir = filename:join(filename:dirname(Simple), "include"), - ?line Options = [{outdir, filename:dirname(Target)}, + {Simple, Target} = get_files(Config, simple, "cond_and_ifdef"), + IncludeDir = filename:join(filename:dirname(Simple), "include"), + Options = [{outdir, filename:dirname(Target)}, {d, need_foo}, {d, foo_value, 42}, {i, IncludeDir}, report], - ?line {ok, simple} = compile:file(Simple, Options), - ?line true = exists(Target), - ?line {hiker, 42} = run(Target, foo, []), - ?line ok = file:delete(Target), - ?line ok = file:del_dir(filename:dirname(Target)), - ?line test_server:timetrap_cancel(Dog), + {ok, simple} = compile:file(Simple, Options), + true = exists(Target), + {hiker, 42} = run(Target, foo, []), + ok = file:delete(Target), + ok = file:del_dir(filename:dirname(Target)), ok. listings(Config) when is_list(Config) -> - Dog = test_server:timetrap(test_server:minutes(8)), - DataDir = ?config(data_dir, Config), - PrivDir = ?config(priv_dir, Config), + DataDir = proplists:get_value(data_dir, Config), + PrivDir = proplists:get_value(priv_dir, Config), ok = do_file_listings(DataDir, PrivDir, [ "simple", "small", "small_maps" ]), - test_server:timetrap_cancel(Dog), ok. do_file_listings(_, _, []) -> ok; @@ -330,6 +311,8 @@ do_file_listings(DataDir, PrivDir, [File|Files]) -> do_listing(Simple, TargetDir, dlife, ".life"), do_listing(Simple, TargetDir, dcg, ".codegen"), do_listing(Simple, TargetDir, dblk, ".block"), + do_listing(Simple, TargetDir, dexcept, ".except"), + do_listing(Simple, TargetDir, dbs, ".bs"), do_listing(Simple, TargetDir, dbool, ".bool"), do_listing(Simple, TargetDir, dtype, ".type"), do_listing(Simple, TargetDir, ddead, ".dead"), @@ -359,159 +342,146 @@ do_file_listings(DataDir, PrivDir, [File|Files]) -> do_file_listings(DataDir,PrivDir,Files). listings_big(Config) when is_list(Config) -> - ?line Dog = test_server:timetrap(test_server:minutes(10)), - ?line DataDir = ?config(data_dir, Config), - ?line PrivDir = ?config(priv_dir, Config), - ?line Big = filename:join(DataDir, big), - ?line TargetDir = filename:join(PrivDir, listings_big), - ?line ok = file:make_dir(TargetDir), - ?line do_listing(Big, TargetDir, 'S'), - ?line do_listing(Big, TargetDir, 'E'), - ?line do_listing(Big, TargetDir, 'P'), - ?line do_listing(Big, TargetDir, dkern, ".kernel"), - - ?line Target = filename:join(TargetDir, big), - {ok,big} = compile:file(Target, [from_asm,{outdir,TargetDir}]), + {Big,Target} = get_files(Config, big, listings_big), + TargetDir = filename:dirname(Target), + do_listing(Big, TargetDir, 'S'), + do_listing(Big, TargetDir, 'E'), + do_listing(Big, TargetDir, 'P'), + do_listing(Big, TargetDir, dkern, ".kernel"), + + TargetNoext = filename:rootname(Target, code:objfile_extension()), + {ok,big} = compile:file(TargetNoext, [from_asm,{outdir,TargetDir}]), %% Cleanup. - ?line ok = file:delete(Target ++ ".beam"), - ?line lists:foreach(fun(F) -> ok = file:delete(F) end, - filelib:wildcard(filename:join(TargetDir, "*"))), - ?line ok = file:del_dir(TargetDir), - ?line test_server:timetrap_cancel(Dog), + ok = file:delete(Target), + lists:foreach(fun(F) -> ok = file:delete(F) end, + filelib:wildcard(filename:join(TargetDir, "*"))), + ok = file:del_dir(TargetDir), ok. other_output(Config) when is_list(Config) -> - ?line Dog = test_server:timetrap(test_server:minutes(8)), - ?line DataDir = ?config(data_dir, Config), - ?line PrivDir = ?config(priv_dir, Config), - ?line Simple = filename:join(DataDir, simple), - ?line TargetDir = filename:join(PrivDir, other_output), - ?line ok = file:make_dir(TargetDir), + {Simple,_Target} = get_files(Config, simple, "other_output"), io:put_chars("to_pp"), - ?line {ok,[],PP} = compile:file(Simple, [to_pp,binary,time]), - ?line [] = [E || E <- PP, - begin - case element(1, E) of - attribute -> false; - function -> false; - eof -> false - end - end], + {ok,[],PP} = compile:file(Simple, [to_pp,binary,time]), + [] = [E || E <- PP, + begin + case element(1, E) of + attribute -> false; + function -> false; + eof -> false + end + end], io:put_chars("to_exp (file)"), - ?line {ok,simple,Expand} = compile:file(Simple, [to_exp,binary,time]), - ?line case Expand of - {simple,Exports,Forms} when is_list(Exports), is_list(Forms) -> ok - end, + {ok,simple,Expand} = compile:file(Simple, [to_exp,binary,time]), + case Expand of + {simple,Exports,Forms} when is_list(Exports), is_list(Forms) -> ok + end, io:put_chars("to_exp (forms)"), - ?line {ok,simple,Expand} = compile:forms(PP, [to_exp,binary,time]), + {ok,simple,Expand} = compile:forms(PP, [to_exp,binary,time]), io:put_chars("to_core (file)"), - ?line {ok,simple,Core} = compile:file(Simple, [to_core,binary,time]), - ?line c_module = element(1, Core), - ?line {ok,_} = core_lint:module(Core), + {ok,simple,Core} = compile:file(Simple, [to_core,binary,time]), + c_module = element(1, Core), + {ok,_} = core_lint:module(Core), io:put_chars("to_core (forms)"), - ?line {ok,simple,Core} = compile:forms(PP, [to_core,binary,time]), + {ok,simple,Core} = compile:forms(PP, [to_core,binary,time]), io:put_chars("to_kernel (file)"), - ?line {ok,simple,Kernel} = compile:file(Simple, [to_kernel,binary,time]), - ?line k_mdef = element(1, Kernel), + {ok,simple,Kernel} = compile:file(Simple, [to_kernel,binary,time]), + k_mdef = element(1, Kernel), io:put_chars("to_kernel (forms)"), - ?line {ok,simple,Kernel} = compile:forms(PP, [to_kernel,binary,time]), + {ok,simple,Kernel} = compile:forms(PP, [to_kernel,binary,time]), io:put_chars("to_asm (file)"), - ?line {ok,simple,Asm} = compile:file(Simple, [to_asm,binary,time]), - ?line {simple,_,_,_,_} = Asm, + {ok,simple,Asm} = compile:file(Simple, [to_asm,binary,time]), + {simple,_,_,_,_} = Asm, io:put_chars("to_asm (forms)"), - ?line {ok,simple,Asm} = compile:forms(PP, [to_asm,binary,time]), + {ok,simple,Asm} = compile:forms(PP, [to_asm,binary,time]), - ?line test_server:timetrap_cancel(Dog), ok. encrypted_abstr(Config) when is_list(Config) -> - ?line Dog = test_server:timetrap(test_server:minutes(10)), - ?line {Simple,Target} = files(Config, "encrypted_abstr"), + {Simple,Target} = get_files(Config, simple, "encrypted_abstr"), Res = case has_crypto() of false -> %% No crypto. - ?line encrypted_abstr_no_crypto(Simple, Target), + encrypted_abstr_no_crypto(Simple, Target), {comment,"The crypto application is missing or broken"}; true -> %% Simulate not having crypto by removing %% the crypto application from the path. - ?line OldPath = code:get_path(), + OldPath = code:get_path(), try - ?line NewPath = OldPath -- [filename:dirname(code:which(crypto))], - ?line (catch crypto:stop()), - ?line code:delete(crypto), - ?line code:purge(crypto), - ?line code:set_path(NewPath), - ?line encrypted_abstr_no_crypto(Simple, Target) + NewPath = OldPath -- [filename:dirname(code:which(crypto))], + (catch crypto:stop()), + code:delete(crypto), + code:purge(crypto), + code:set_path(NewPath), + encrypted_abstr_no_crypto(Simple, Target) after code:set_path(OldPath) end, %% Now run the tests that require crypto. - ?line encrypted_abstr_1(Simple, Target), - ?line ok = file:delete(Target), - ?line ok = file:del_dir(filename:dirname(Target)) + encrypted_abstr_1(Simple, Target), + ok = file:delete(Target), + ok = file:del_dir(filename:dirname(Target)) end, %% Cleanup. - ?line test_server:timetrap_cancel(Dog), Res. encrypted_abstr_1(Simple, Target) -> - ?line TargetDir = filename:dirname(Target), - ?line Key = "ablurf123BX#$;3", - ?line install_crypto_key(Key), - ?line {ok,simple} = compile:file(Simple, + TargetDir = filename:dirname(Target), + Key = "ablurf123BX#$;3", + install_crypto_key(Key), + {ok,simple} = compile:file(Simple, [debug_info,{debug_info_key,Key}, {outdir,TargetDir}]), - ?line verify_abstract(Target), + verify_abstract(Target), - ?line {ok,simple} = compile:file(Simple, + {ok,simple} = compile:file(Simple, [{debug_info_key,Key}, {outdir,TargetDir}]), - ?line verify_abstract(Target), + verify_abstract(Target), - ?line {ok,simple} = compile:file(Simple, + {ok,simple} = compile:file(Simple, [debug_info,{debug_info_key,{des3_cbc,Key}}, {outdir,TargetDir}]), - ?line verify_abstract(Target), + verify_abstract(Target), - ?line {ok,{simple,[{compile_info,CInfo}]}} = + {ok,{simple,[{compile_info,CInfo}]}} = beam_lib:chunks(Target, [compile_info]), - ?line {value,{_,Opts}} = lists:keysearch(options, 1, CInfo), - ?line {value,{_,'********'}} = lists:keysearch(debug_info_key, 1, Opts), + {_,Opts} = lists:keyfind(options, 1, CInfo), + {_,'********'} = lists:keyfind(debug_info_key, 1, Opts), %% Try some illegal forms of crypto keys. - ?line error = compile:file(Simple, + error = compile:file(Simple, [debug_info,{debug_info_key,{blurf,"ss"}},report]), - ?line error = compile:file(Simple, + error = compile:file(Simple, [debug_info,{debug_info_key,{blurf,1,"ss"}},report]), - ?line error = compile:file(Simple, + error = compile:file(Simple, [debug_info,{debug_info_key,42},report]), %% Place the crypto key in .erlang.crypt. - ?line beam_lib:clear_crypto_key_fun(), - ?line {ok,OldCwd} = file:get_cwd(), - ?line ok = file:set_cwd(TargetDir), - - ?line error = compile:file(Simple, [encrypt_debug_info,report]), - - ?line NewKey = "better use another key here", - ?line write_crypt_file(["[{debug_info,des3_cbc,simple,\"",NewKey,"\"}].\n"]), - ?line {ok,simple} = compile:file(Simple, [encrypt_debug_info,report]), - ?line verify_abstract("simple.beam"), - ?line ok = file:delete(".erlang.crypt"), - ?line beam_lib:clear_crypto_key_fun(), - ?line {error,beam_lib,{key_missing_or_invalid,"simple.beam",abstract_code}} = + beam_lib:clear_crypto_key_fun(), + {ok,OldCwd} = file:get_cwd(), + ok = file:set_cwd(TargetDir), + + error = compile:file(Simple, [encrypt_debug_info,report]), + + NewKey = "better use another key here", + write_crypt_file(["[{debug_info,des3_cbc,simple,\"",NewKey,"\"}].\n"]), + {ok,simple} = compile:file(Simple, [encrypt_debug_info,report]), + verify_abstract("simple.beam"), + ok = file:delete(".erlang.crypt"), + beam_lib:clear_crypto_key_fun(), + {error,beam_lib,{key_missing_or_invalid,"simple.beam",abstract_code}} = beam_lib:chunks("simple.beam", [abstract_code]), - ?line ok = file:set_cwd(OldCwd), + ok = file:set_cwd(OldCwd), %% Test key compatibility by reading a BEAM file produced before %% the update to the new crypto functions. @@ -532,9 +502,9 @@ write_crypt_file(Contents0) -> encrypted_abstr_no_crypto(Simple, Target) -> io:format("simpe: ~p~n", [Simple]), - ?line TargetDir = filename:dirname(Target), - ?line Key = "ablurf123BX#$;3", - ?line error = compile:file(Simple, + TargetDir = filename:dirname(Target), + Key = "ablurf123BX#$;3", + error = compile:file(Simple, [debug_info,{debug_info_key,Key}, {outdir,TargetDir},report]), ok. @@ -562,7 +532,7 @@ install_crypto_key(Key) -> %% Miscellanous tests, mainly to get better coverage. cover(Config) when is_list(Config) -> - ?line io:format("~p\n", [compile:options()]), + io:format("~p\n", [compile:options()]), ok. do_listing(Source, TargetDir, Type) -> @@ -573,31 +543,31 @@ do_listing(Source, TargetDir, Type, Ext) -> [Source, TargetDir, Type, Ext]), case compile:file(Source, [Type, time, {outdir, TargetDir}]) of {ok, _} -> ok; - Other -> test_server:fail({unexpected_result, Other}) + Other -> ct:fail({unexpected_result, Other}) end, SourceBase = filename:rootname(filename:basename(Source)), Target = filename:join(TargetDir, SourceBase ++ Ext), true = exists(Target). -files(Config, Name) -> - ?line code:delete(simple), - ?line code:purge(simple), - ?line DataDir = ?config(data_dir, Config), - ?line PrivDir = ?config(priv_dir, Config), - ?line Simple = filename:join(DataDir, "simple"), - ?line TargetDir = filename:join(PrivDir, Name), - ?line ok = file:make_dir(TargetDir), - ?line Target = filename:join(TargetDir, "simple"++code:objfile_extension()), - {Simple, Target}. - +get_files(Config, Module, OutputName) -> + code:delete(Module), + code:purge(Module), + DataDir = proplists:get_value(data_dir, Config), + PrivDir = proplists:get_value(priv_dir, Config), + Src = filename:join(DataDir, atom_to_list(Module)), + TargetDir = filename:join(PrivDir, OutputName), + ok = file:make_dir(TargetDir), + File = atom_to_list(Module) ++ code:objfile_extension(), + Target = filename:join(TargetDir, File), + {Src, Target}. run(Target, Func, Args) -> - ?line Module = list_to_atom(filename:rootname(filename:basename(Target))), - ?line {module, Module} = code:load_abs(filename:rootname(Target)), - ?line Result = (catch apply(Module, Func, Args)), - ?line true = code:delete(Module), - ?line false = code:purge(Module), + Module = list_to_atom(filename:rootname(filename:basename(Target))), + {module, Module} = code:load_abs(filename:rootname(Target)), + Result = (catch apply(Module, Func, Args)), + true = code:delete(Module), + false = code:purge(Module), Result. exists(Name) -> @@ -607,49 +577,27 @@ exists(Name) -> end. -%% Tests that the compiler does not accept -%% bad use of records. -bad_record_use1(Config) when is_list(Config) -> - ?line {ok, Cwd} = file:get_cwd(), - ?line file:set_cwd(?config(data_dir, Config)), - ?line true=exists("bad_record_use.erl"), - ?line Ret=c:c(bad_record_use), - ?line file:set_cwd(Cwd), - ?line error=Ret, - ok. - -%% Tests that the compiler does not accept -%% bad use of records. -bad_record_use2(Config) when is_list(Config) -> - ?line {ok, Cwd} = file:get_cwd(), - ?line file:set_cwd(?config(data_dir, Config)), - ?line true=exists("bad_record_use2.erl"), - ?line Ret=c:c(bad_record_use), - ?line file:set_cwd(Cwd), - ?line error=Ret, - ok. - strict_record(Config) when is_list(Config) -> - ?line Priv = ?config(priv_dir, Config), - ?line file:set_cwd(?config(data_dir, Config)), - ?line Opts = [{outdir,Priv},report_errors], + Priv = proplists:get_value(priv_dir, Config), + ok = file:set_cwd(proplists:get_value(data_dir, Config)), + Opts = [{outdir,Priv},report_errors], M = record_access, - ?line {ok,M} = c:c(M, [strict_record_tests|Opts]), - ?line Turtle = test_strict(), + {ok,M} = c:c(M, [strict_record_tests|Opts]), + Turtle = test_strict(), - ?line {ok,M} = c:c(M, [no_strict_record_tests|Opts]), - ?line Turtle = test_sloppy(), + {ok,M} = c:c(M, [no_strict_record_tests|Opts]), + Turtle = test_sloppy(), %% The option first given wins. - ?line {ok,M} = c:c(M, [no_strict_record_tests,strict_record_tests|Opts]), - ?line Turtle = test_sloppy(), - ?line {ok,M} = c:c(M, [strict_record_tests,no_strict_record_tests|Opts]), - ?line Turtle = test_strict(), + {ok,M} = c:c(M, [no_strict_record_tests,strict_record_tests|Opts]), + Turtle = test_sloppy(), + {ok,M} = c:c(M, [strict_record_tests,no_strict_record_tests|Opts]), + Turtle = test_strict(), %% Default (possibly influenced by ERL_COMPILER_OPTIONS). - ?line {ok,M} = c:c(M, [{outdir,Priv},report_errors]), - ?line try + {ok,M} = c:c(M, [{outdir,Priv},report_errors]), + try {1,2} = record_access:test(Turtle), {comment,"Default: no_strict_record_tests"} catch @@ -659,7 +607,7 @@ strict_record(Config) when is_list(Config) -> test_strict() -> Turtle = record_access:turtle(), - ?line try + try record_access:test(Turtle) catch error:{badrecord,tortoise} -> @@ -673,19 +621,19 @@ test_sloppy() -> Turtle. missing_testheap(Config) when is_list(Config) -> - DataDir = ?config(data_dir, Config), - PrivDir = ?config(priv_dir, Config), + DataDir = proplists:get_value(data_dir, Config), + PrivDir = proplists:get_value(priv_dir, Config), Opts = [{outdir,PrivDir}], OldPath = code:get_path(), try code:add_patha(PrivDir), c:c(filename:join(DataDir, "missing_testheap1"), Opts), c:c(filename:join(DataDir, "missing_testheap2"), Opts), - ?line ok = test(fun() -> - missing_testheap1:f({a,self()},{state,true,b}) - end, {a,b}), - ?line ok = test(fun() -> - missing_testheap2:f({a,self()},16#80000000) end, + ok = test(fun() -> + missing_testheap1:f({a,self()},{state,true,b}) + end, {a,b}), + ok = test(fun() -> + missing_testheap2:f({a,self()},16#80000000) end, bigger) after code:set_path(OldPath), @@ -706,47 +654,47 @@ test(Iter, Fun, Result, Filler) -> test(Iter-1, Fun, Result, [0|Filler]); {result, Other} -> io:format("Expected ~p; got ~p~n", [Result, Other]), - test_server:fail() + ct:fail(failed) end. init(ReplyTo, Fun, _Filler) -> ReplyTo ! {result, Fun()}. env(Config) when is_list(Config) -> - ?line {Simple,Target} = files(Config, "file_1"), - ?line {ok,Cwd} = file:get_cwd(), - ?line ok = file:set_cwd(filename:dirname(Target)), + {Simple,Target} = get_files(Config, simple, env), + {ok,Cwd} = file:get_cwd(), + ok = file:set_cwd(filename:dirname(Target)), true = os:putenv("ERL_COMPILER_OPTIONS", "binary"), try env_1(Simple, Target) after true = os:putenv("ERL_COMPILER_OPTIONS", "ignore_me"), - file:set_cwd(Cwd), - file:delete(Target), - file:del_dir(filename:dirname(Target)) + file:set_cwd(Cwd), + file:delete(Target), + file:del_dir(filename:dirname(Target)) end, ok. env_1(Simple, Target) -> %% file - ?line {ok,simple,<<_/binary>>} = compile:file(Simple), - ?line {ok,simple} = compile:noenv_file(Simple, [debug_info]), - ?line true = exists(Target), - ?line {ok,{simple,[{abstract_code,Abstr0}]}} = + {ok,simple,<<_/binary>>} = compile:file(Simple), + {ok,simple} = compile:noenv_file(Simple, [debug_info]), + true = exists(Target), + {ok,{simple,[{abstract_code,Abstr0}]}} = beam_lib:chunks(Target, [abstract_code]), - ?line {raw_abstract_v1,Forms} = Abstr0, + {raw_abstract_v1,Forms} = Abstr0, %% forms - ?line true = os:putenv("ERL_COMPILER_OPTIONS", "strong_validation"), - ?line {ok,simple} = compile:forms(Forms), - ?line {ok,simple,<<"FOR1",_/binary>>} = compile:noenv_forms(Forms, []), + true = os:putenv("ERL_COMPILER_OPTIONS", "strong_validation"), + {ok,simple} = compile:forms(Forms), + {ok,simple,<<"FOR1",_/binary>>} = compile:noenv_forms(Forms, []), %% output_generated - ?line false = compile:output_generated([]), - ?line true = compile:noenv_output_generated([]), + false = compile:output_generated([]), + true = compile:noenv_output_generated([]), - ?line ok = file:delete(Target), + ok = file:delete(Target), ok. @@ -754,7 +702,7 @@ env_1(Simple, Target) -> %% compile the generated Core Erlang files. core(Config) when is_list(Config) -> - PrivDir = ?config(priv_dir, Config), + PrivDir = proplists:get_value(priv_dir, Config), Outdir = filename:join(PrivDir, "core"), ok = file:make_dir(Outdir), @@ -817,15 +765,13 @@ compile_forms(Forms, Opts) -> %% run .S through the compiler again. asm(Config) when is_list(Config) -> - ?line Dog = test_server:timetrap(test_server:minutes(20)), - ?line PrivDir = ?config(priv_dir, Config), - ?line Outdir = filename:join(PrivDir, "asm"), - ?line ok = file:make_dir(Outdir), - - ?line Wc = filename:join(filename:dirname(code:which(?MODULE)), "*.beam"), - ?line TestBeams = filelib:wildcard(Wc), - ?line Res = test_lib:p_run(fun(F) -> do_asm(F, Outdir) end, TestBeams), - ?line test_server:timetrap_cancel(Dog), + PrivDir = proplists:get_value(priv_dir, Config), + Outdir = filename:join(PrivDir, "asm"), + ok = file:make_dir(Outdir), + + Wc = filename:join(filename:dirname(code:which(?MODULE)), "*.beam"), + TestBeams = filelib:wildcard(Wc), + Res = test_lib:p_run(fun(F) -> do_asm(F, Outdir) end, TestBeams), Res. @@ -853,7 +799,7 @@ do_asm(Beam, Outdir) -> end. sys_pre_attributes(Config) -> - DataDir = ?config(data_dir, Config), + DataDir = proplists:get_value(data_dir, Config), File = filename:join(DataDir, "attributes.erl"), Mod = attributes, CommonOpts = [binary,report,verbose, @@ -885,8 +831,8 @@ sys_pre_attributes(Config) -> %% Test the dialyzer option to cover more code. dialyzer(Config) -> - Priv = ?config(priv_dir, Config), - file:set_cwd(?config(data_dir, Config)), + Priv = proplists:get_value(priv_dir, Config), + ok = file:set_cwd(proplists:get_value(data_dir, Config)), Opts = [{outdir,Priv},report_errors], M = dialyzer_test, {ok,M} = c:c(M, [dialyzer|Opts]), diff --git a/lib/compiler/test/compile_SUITE_data/bad_record_use.erl b/lib/compiler/test/compile_SUITE_data/bad_record_use.erl deleted file mode 100644 index 0fb6fc3045..0000000000 --- a/lib/compiler/test/compile_SUITE_data/bad_record_use.erl +++ /dev/null @@ -1,29 +0,0 @@ -%% -%% %CopyrightBegin% -%% -%% Copyright Ericsson AB 1998-2009. All Rights Reserved. -%% -%% Licensed under the Apache License, Version 2.0 (the "License"); -%% you may not use this file except in compliance with the License. -%% You may obtain a copy of the License at -%% -%% http://www.apache.org/licenses/LICENSE-2.0 -%% -%% Unless required by applicable law or agreed to in writing, software -%% distributed under the License is distributed on an "AS IS" BASIS, -%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied. -%% See the License for the specific language governing permissions and -%% limitations under the License. -%% -%% %CopyrightEnd% -%% --module(bad_record_use). --export([test/0]). - --record(bad_use, {a=undefined, - b=undefined, - c=undefined}). - -test() -> - NewRecord=#bad_use{a=1, b=2, a=2}. - diff --git a/lib/compiler/test/compile_SUITE_data/bad_record_use2.erl b/lib/compiler/test/compile_SUITE_data/bad_record_use2.erl deleted file mode 100644 index 7c898af00f..0000000000 --- a/lib/compiler/test/compile_SUITE_data/bad_record_use2.erl +++ /dev/null @@ -1,30 +0,0 @@ -%% -%% %CopyrightBegin% -%% -%% Copyright Ericsson AB 1998-2009. All Rights Reserved. -%% -%% Licensed under the Apache License, Version 2.0 (the "License"); -%% you may not use this file except in compliance with the License. -%% You may obtain a copy of the License at -%% -%% http://www.apache.org/licenses/LICENSE-2.0 -%% -%% Unless required by applicable law or agreed to in writing, software -%% distributed under the License is distributed on an "AS IS" BASIS, -%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied. -%% See the License for the specific language governing permissions and -%% limitations under the License. -%% -%% %CopyrightEnd% -%% --module(bad_record_use2). --export([test/0]). - --record(bad_use, {a=undefined, - b=undefined, - c=undefined}). - -test() -> - R=#bad_use{a=1, b=2}, - R2=R#bad_use{a=1, b=2, a=2}, - ok. diff --git a/lib/compiler/test/core_SUITE.erl b/lib/compiler/test/core_SUITE.erl index 25f8564ce4..22f6443a77 100644 --- a/lib/compiler/test/core_SUITE.erl +++ b/lib/compiler/test/core_SUITE.erl @@ -29,21 +29,20 @@ bs_shadowed_size_var/1 ]). --include_lib("test_server/include/test_server.hrl"). +-include_lib("common_test/include/ct.hrl"). -define(comp(N), N(Config) when is_list(Config) -> try_it(N, Config)). init_per_testcase(Case, Config) when is_atom(Case), is_list(Config) -> - Dog = test_server:timetrap(?t:minutes(5)), - [{watchdog,Dog}|Config]. + Config. end_per_testcase(Case, Config) when is_atom(Case), is_list(Config) -> - Dog = ?config(watchdog, Config), - ?t:timetrap_cancel(Dog), ok. -suite() -> [{ct_hooks,[ts_install_cth]}]. +suite() -> + [{ct_hooks,[ts_install_cth]}, + {timetrap,{minutes,5}}]. all() -> test_lib:recompile(?MODULE), @@ -86,7 +85,8 @@ end_per_group(_GroupName, Config) -> try_it(Mod, Conf) -> - Src = filename:join(?config(data_dir, Conf), atom_to_list(Mod)), + Src = filename:join(proplists:get_value(data_dir, Conf), + atom_to_list(Mod)), compile_and_load(Src, []), compile_and_load(Src, [no_copt]). diff --git a/lib/compiler/test/core_fold_SUITE.erl b/lib/compiler/test/core_fold_SUITE.erl index 016ea9d0d9..ee2a2c523f 100644 --- a/lib/compiler/test/core_fold_SUITE.erl +++ b/lib/compiler/test/core_fold_SUITE.erl @@ -29,7 +29,7 @@ -export([foo/0,foo/1,foo/2,foo/3]). --include_lib("test_server/include/test_server.hrl"). +-include_lib("common_test/include/ct.hrl"). suite() -> [{ct_hooks,[ts_install_cth]}]. @@ -61,8 +61,8 @@ end_per_group(_GroupName, Config) -> t_element(Config) when is_list(Config) -> X = make_ref(), - ?line X = id(element(1, {X,y,z})), - ?line b = id(element(2, {a,b,c,d})), + X = id(element(1, {X,y,z})), + b = id(element(2, {a,b,c,d})), (fun() -> case {a,#{k=>X}} of {a,#{k:=X}}=Tuple -> @@ -73,21 +73,21 @@ t_element(Config) when is_list(Config) -> %% No optimization, but should work. Tuple = id({x,y,z}), Pos = id(3), - ?line x = id(element(1, Tuple)), - ?line c = id(element(Pos, {a,b,c,d})), - ?line X = id(element(Pos, {a,b,X,d})), - ?line z = id(element(Pos, Tuple)), + x = id(element(1, Tuple)), + c = id(element(Pos, {a,b,c,d})), + X = id(element(Pos, {a,b,X,d})), + z = id(element(Pos, Tuple)), %% Calls that will fail. - ?line {'EXIT',{badarg,_}} = (catch element(5, {a,b,c,d})), - ?line {'EXIT',{badarg,_}} = (catch element(5, {a,b,X,d})), - ?line {'EXIT',{badarg,_}} = (catch element(5.0, {a,b,X,d})), + {'EXIT',{badarg,_}} = (catch element(5, {a,b,c,d})), + {'EXIT',{badarg,_}} = (catch element(5, {a,b,X,d})), + {'EXIT',{badarg,_}} = (catch element(5.0, {a,b,X,d})), {'EXIT',{badarg,_}} = (catch element(2, not_a_tuple)), {'EXIT',{badarg,_}} = (catch element(2, [])), {'EXIT',{badarg,_}} = (catch element(2, Tuple == 3)), case id({a,b,c}) of {_,_,_}=Tup -> - ?line {'EXIT',{badarg,_}} = (catch element(4, Tup)) + {'EXIT',{badarg,_}} = (catch element(4, Tup)) end, {'EXIT',{badarg,_}} = (catch element(1, tuple_size(Tuple))), @@ -96,16 +96,16 @@ t_element(Config) when is_list(Config) -> setelement(Config) when is_list(Config) -> X = id(b), New = id([1,2,3]), - ?line {y,b,c} = id(setelement(1, {a,b,c}, y)), - ?line {y,b,c} = id(setelement(1, {a,X,c}, y)), - ?line {a,y,c} = id(setelement(2, {a,X,c}, y)), - ?line {a,[1,2,3],c} = id(setelement(2, {a,b,c}, New)), - ?line {a,[1,2,3],c} = id(setelement(2, {a,X,c}, New)), - ?line {a,b,[1,2,3]} = id(setelement(3, {a,b,c}, New)), - ?line {a,b,[1,2,3]} = id(setelement(3, {a,X,c}, New)), + {y,b,c} = id(setelement(1, {a,b,c}, y)), + {y,b,c} = id(setelement(1, {a,X,c}, y)), + {a,y,c} = id(setelement(2, {a,X,c}, y)), + {a,[1,2,3],c} = id(setelement(2, {a,b,c}, New)), + {a,[1,2,3],c} = id(setelement(2, {a,X,c}, New)), + {a,b,[1,2,3]} = id(setelement(3, {a,b,c}, New)), + {a,b,[1,2,3]} = id(setelement(3, {a,X,c}, New)), - ?line {'EXIT',{badarg,_}} = (catch setelement_crash({a,b,c,d,e,f})), - ?line error = setelement_crash_2({a,b,c,d,e,f}, <<42>>), + {'EXIT',{badarg,_}} = (catch setelement_crash({a,b,c,d,e,f})), + error = setelement_crash_2({a,b,c,d,e,f}, <<42>>), {'EXIT',{badarg,_}} = (catch setelement(1, not_a_tuple, New)), {'EXIT',{badarg,_}} = (catch setelement(3, {a,b}, New)), @@ -132,19 +132,19 @@ setelement_crash_2(Tuple, Bin) -> t_length(Config) when is_list(Config) -> Blurf = id({blurf,a,b}), Tail = id([42,43,44,45]), - ?line 0 = id(length([])), - ?line 1 = id(length([x])), - ?line 2 = id(length([x,Blurf])), - ?line 4 = id(length([x,Blurf,a,b])), + 0 = id(length([])), + 1 = id(length([x])), + 2 = id(length([x,Blurf])), + 4 = id(length([x,Blurf,a,b])), %% No or partial optimization. - ?line 4 = length(Tail), - ?line 5 = id(length([x|Tail])), + 4 = length(Tail), + 5 = id(length([x|Tail])), %% Will fail. - ?line {'EXIT',{badarg,_}} = (catch id(length([a,b|c]))), - ?line {'EXIT',{badarg,_}} = (catch id(length([a,Blurf|c]))), - ?line {'EXIT',{badarg,_}} = (catch id(length(atom))), + {'EXIT',{badarg,_}} = (catch id(length([a,b|c]))), + {'EXIT',{badarg,_}} = (catch id(length([a,Blurf|c]))), + {'EXIT',{badarg,_}} = (catch id(length(atom))), ok. @@ -156,34 +156,34 @@ t_length(Config) when is_list(Config) -> append(Config) when is_list(Config) -> A = id(0), - ?line [a,b,c,d,e,f,g,h,i,j,k] = id(?APPEND([a,b,c,d,e,f],[g,h,i,j,k])), - ?line [a,b,c,d,e] = id(?APPEND([a,b,c],id([d,e]))), - ?line [0,1,2,3,4,5,6] = id(?APPEND([A,1,2,3],[4,5,6])), - ?line {'EXIT',{badarg,_}} = (catch id(?APPEND([A|blurf],[4,5,6]))), + [a,b,c,d,e,f,g,h,i,j,k] = id(?APPEND([a,b,c,d,e,f],[g,h,i,j,k])), + [a,b,c,d,e] = id(?APPEND([a,b,c],id([d,e]))), + [0,1,2,3,4,5,6] = id(?APPEND([A,1,2,3],[4,5,6])), + {'EXIT',{badarg,_}} = (catch id(?APPEND([A|blurf],[4,5,6]))), ok. t_apply(Config) when is_list(Config) -> - ?line ok = apply(?MODULE, foo, []), - ?line 4 = apply(?MODULE, foo, [3]), - ?line 7 = apply(?MODULE, foo, [3,4]), - ?line 12 = apply(?MODULE, foo, [id(8),4]), - ?line 21 = apply(?MODULE, foo, [8,id(9),4]), - ?line 20 = apply(?MODULE, foo, [8,8,id(4)]), - ?line 24 = apply(?MODULE, foo, [id(10),10,4]), + ok = apply(?MODULE, foo, []), + 4 = apply(?MODULE, foo, [3]), + 7 = apply(?MODULE, foo, [3,4]), + 12 = apply(?MODULE, foo, [id(8),4]), + 21 = apply(?MODULE, foo, [8,id(9),4]), + 20 = apply(?MODULE, foo, [8,8,id(4)]), + 24 = apply(?MODULE, foo, [id(10),10,4]), M = id(?MODULE), - ?line ok = apply(M, foo, []), - ?line 4 = apply(M, foo, [3]), - ?line 16.0 = apply(M, foo, [12.0,4]), + ok = apply(M, foo, []), + 4 = apply(M, foo, [3]), + 16.0 = apply(M, foo, [12.0,4]), %% Will fail. - ?line {'EXIT',{badarg,_}} = (catch apply([a,b,c], foo, [])), - ?line {'EXIT',{badarg,_}} = (catch apply(42, foo, [])), - ?line {'EXIT',{badarg,_}} = (catch apply(?MODULE, 45, [xx])), - ?line {'EXIT',{badarg,_}} = (catch apply(?MODULE, foo, {a,b})), - ?line {'EXIT',{badarg,_}} = (catch apply(M, M, [1009|10010])), - ?line {'EXIT',{badarg,_}} = (catch apply(?MODULE, foo, [10000|9999])), - ?line {'EXIT',{badarg,_}} = (catch apply(?MODULE, foo, a)), + {'EXIT',{badarg,_}} = (catch apply([a,b,c], foo, [])), + {'EXIT',{badarg,_}} = (catch apply(42, foo, [])), + {'EXIT',{badarg,_}} = (catch apply(?MODULE, 45, [xx])), + {'EXIT',{badarg,_}} = (catch apply(?MODULE, foo, {a,b})), + {'EXIT',{badarg,_}} = (catch apply(M, M, [1009|10010])), + {'EXIT',{badarg,_}} = (catch apply(?MODULE, foo, [10000|9999])), + {'EXIT',{badarg,_}} = (catch apply(?MODULE, foo, a)), ok. @@ -210,13 +210,13 @@ bifs(Config) when is_list(Config) -> -define(CMP_DIFF(A0, B), (fun(A) -> false = A == B, true = A /= B end)(id(A0))). eq(Config) when is_list(Config) -> - ?line ?CMP_SAME([a,b,c], [a,b,c]), - ?line ?CMP_SAME([42.0], [42.0]), - ?line ?CMP_SAME([42], [42]), - ?line ?CMP_SAME([42.0], [42]), + ?CMP_SAME([a,b,c], [a,b,c]), + ?CMP_SAME([42.0], [42.0]), + ?CMP_SAME([42], [42]), + ?CMP_SAME([42.0], [42]), - ?line ?CMP_DIFF(a, [a]), - ?line ?CMP_DIFF(a, {1,2,3}), + ?CMP_DIFF(a, [a]), + ?CMP_DIFF(a, {1,2,3}), ?CMP_SAME(#{a=>1.0,b=>2}, #{b=>2.0,a=>1}), ?CMP_SAME(#{a=>[1.0],b=>[2]}, #{b=>[2.0],a=>[1]}), @@ -232,7 +232,7 @@ eq(Config) when is_list(Config) -> %% OTP-7117. nested_call_in_case(Config) when is_list(Config) -> - PrivDir = ?config(priv_dir, Config), + PrivDir = proplists:get_value(priv_dir, Config), Dir = test_lib:get_data_dir(Config), Core = filename:join(Dir, "nested_call_in_case"), Opts = [from_core,{outdir,PrivDir}|test_lib:opt_opts(?MODULE)], @@ -265,12 +265,12 @@ do_guard_try_catch(K, V) -> -record(cover_opt_guard_try, {list=[]}). coverage(Config) when is_list(Config) -> - ?line {'EXIT',{{case_clause,{a,b,c}},_}} = + {'EXIT',{{case_clause,{a,b,c}},_}} = (catch cover_will_match_list_type({a,b,c})), - ?line {'EXIT',{{case_clause,{a,b,c,d}},_}} = + {'EXIT',{{case_clause,{a,b,c,d}},_}} = (catch cover_will_match_list_type({a,b,c,d})), - ?line a = cover_remove_non_vars_alias({a,b,c}), - ?line error = cover_will_match_lit_list(), + a = cover_remove_non_vars_alias({a,b,c}), + error = cover_will_match_lit_list(), {ok,[a]} = cover_is_safe_bool_expr(a), ok = cover_opt_guard_try(#cover_opt_guard_try{list=[a]}), @@ -347,7 +347,7 @@ bsm_an_inlined(<<_:8>>, _) -> ok; bsm_an_inlined(_, _) -> error. unused_multiple_values_error(Config) when is_list(Config) -> - PrivDir = ?config(priv_dir, Config), + PrivDir = proplists:get_value(priv_dir, Config), Dir = test_lib:get_data_dir(Config), Core = filename:join(Dir, "unused_multiple_values_error"), Opts = [no_copt,clint,return,from_core,{outdir,PrivDir} diff --git a/lib/compiler/test/error_SUITE.erl b/lib/compiler/test/error_SUITE.erl index 2962e3ff77..dd2e766599 100644 --- a/lib/compiler/test/error_SUITE.erl +++ b/lib/compiler/test/error_SUITE.erl @@ -18,7 +18,7 @@ %% %CopyrightEnd% -module(error_SUITE). --include_lib("test_server/include/test_server.hrl"). +-include_lib("common_test/include/ct.hrl"). -export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, init_per_group/2,end_per_group/2, @@ -65,7 +65,7 @@ bif_clashes(Config) when is_list(Config) -> [return_warnings], {error, [{4, erl_lint,{call_to_redefined_old_bif,{length,1}}}], []} }], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), Ts1 = [{bif_clashes2, <<" -export([t/0]). @@ -76,7 +76,7 @@ bif_clashes(Config) when is_list(Config) -> [return_warnings], {error, [{3, erl_lint,{redefine_old_bif_import,{length,1}}}], []} }], - ?line [] = run(Config, Ts1), + [] = run(Config, Ts1), Ts00 = [{bif_clashes3, <<" -export([t/0]). @@ -89,7 +89,7 @@ bif_clashes(Config) when is_list(Config) -> ">>, [return_warnings], []}], - ?line [] = run(Config, Ts00), + [] = run(Config, Ts00), Ts11 = [{bif_clashes4, <<" -export([t/0]). @@ -100,7 +100,7 @@ bif_clashes(Config) when is_list(Config) -> ">>, [return_warnings], []}], - ?line [] = run(Config, Ts11), + [] = run(Config, Ts11), Ts000 = [{bif_clashes5, <<" -export([t/0]). @@ -113,7 +113,7 @@ bif_clashes(Config) when is_list(Config) -> [return_warnings], {warning, [{4, erl_lint,{call_to_redefined_bif,{binary_part,3}}}]} }], - ?line [] = run(Config, Ts000), + [] = run(Config, Ts000), Ts111 = [{bif_clashes6, <<" -export([t/0]). @@ -124,7 +124,7 @@ bif_clashes(Config) when is_list(Config) -> [return_warnings], {warning, [{3, erl_lint,{redefine_bif_import,{binary_part,3}}}]} }], - ?line [] = run(Config, Ts111), + [] = run(Config, Ts111), Ts2 = [{bif_clashes7, <<" -export([t/0]). @@ -139,7 +139,7 @@ bif_clashes(Config) when is_list(Config) -> {error, [{7,erl_lint,{define_import,{length,1}}}], []} }], - ?line [] = run2(Config, Ts2), + [] = run2(Config, Ts2), Ts3 = [{bif_clashes8, <<" -export([t/1]). @@ -153,7 +153,7 @@ bif_clashes(Config) when is_list(Config) -> {error, [{4,erl_lint,{illegal_guard_local_call,{length,1}}}], []} }], - ?line [] = run2(Config, Ts3), + [] = run2(Config, Ts3), Ts4 = [{bif_clashes9, <<" -export([t/1]). @@ -166,7 +166,7 @@ bif_clashes(Config) when is_list(Config) -> {error, [{5,erl_lint,{illegal_guard_local_call,{length,1}}}], []} }], - ?line [] = run2(Config, Ts4), + [] = run2(Config, Ts4), ok. @@ -175,23 +175,23 @@ bif_clashes(Config) when is_list(Config) -> %% Tests that a head mismatch is reported on the correct line (OTP-2125). head_mismatch_line(Config) when is_list(Config) -> - ?line [E|_] = get_compilation_errors(Config, "head_mismatch_line"), - ?line {26, Mod, Reason} = E, - ?line Mod:format_error(Reason), + [E|_] = get_compilation_errors(Config, "head_mismatch_line"), + {26, Mod, Reason} = E, + Mod:format_error(Reason), ok. %% Compiles a test file and returns the list of errors. get_compilation_errors(Config, Filename) -> - ?line DataDir = ?config(data_dir, Config), - ?line File = filename:join(DataDir, Filename), - ?line {error, [{_Name, E}|_], []} = compile:file(File, [return_errors]), + DataDir = proplists:get_value(data_dir, Config), + File = filename:join(DataDir, Filename), + {error, [{_Name, E}|_], []} = compile:file(File, [return_errors]), E. warnings_as_errors(Config) when is_list(Config) -> - ?line TestFile = test_filename(Config), - ?line BeamFile = filename:rootname(TestFile, ".erl") ++ ".beam", - ?line OutDir = ?config(priv_dir, Config), + TestFile = test_filename(Config), + BeamFile = filename:rootname(TestFile, ".erl") ++ ".beam", + OutDir = proplists:get_value(priv_dir, Config), Ts1 = [{warnings_as_errors, <<" @@ -203,8 +203,8 @@ warnings_as_errors(Config) when is_list(Config) -> {error, [], [{3,erl_lint,{unused_var,'A'}}]} }], - ?line [] = run(Ts1, TestFile, write_beam), - ?line false = filelib:is_regular(BeamFile), + [] = run(Ts1, TestFile, write_beam), + false = filelib:is_regular(BeamFile), Ts2 = [{warning_unused_var, <<" @@ -216,9 +216,9 @@ warnings_as_errors(Config) when is_list(Config) -> {warning, [{3,erl_lint,{unused_var,'A'}}]} }], - ?line [] = run(Ts2, TestFile, write_beam), - ?line true = filelib:is_regular(BeamFile), - ?line ok = file:delete(BeamFile), + [] = run(Ts2, TestFile, write_beam), + true = filelib:is_regular(BeamFile), + ok = file:delete(BeamFile), ok. @@ -295,7 +295,7 @@ bad_utf8(Config) -> run(Config, Tests) -> - ?line File = test_filename(Config), + File = test_filename(Config), run(Tests, File, dont_write_beam). run(Tests, File, WriteBeam) -> @@ -304,7 +304,7 @@ run(Tests, File, WriteBeam) -> E -> BadL; Bad -> - ?t:format("~nTest ~p failed. Expected~n ~p~n" + io:format("~nTest ~p failed. Expected~n ~p~n" "but got~n ~p~n", [N, E, Bad]), fail() end @@ -312,7 +312,7 @@ run(Tests, File, WriteBeam) -> lists:foldl(F, [], Tests). run2(Config, Tests) -> - ?line File = test_filename(Config), + File = test_filename(Config), run2(Tests, File, dont_write_beam). run2(Tests, File, WriteBeam) -> @@ -321,7 +321,7 @@ run2(Tests, File, WriteBeam) -> E -> BadL; Bad -> - ?t:format("~nTest ~p failed. Expected~n ~p~n" + io:format("~nTest ~p failed. Expected~n ~p~n" "but got~n ~p~n", [N, E, Bad]), fail() end @@ -338,56 +338,45 @@ filter(X) -> test_filename(Conf) -> Filename = ["errors_test_",test_lib:uniq(),".erl"], - DataDir = ?config(priv_dir, Conf), + DataDir = proplists:get_value(priv_dir, Conf), filename:join(DataDir, Filename). run_test(Test0, File, Warnings, WriteBeam) -> ModName = filename:rootname(filename:basename(File), ".erl"), Mod = list_to_atom(ModName), Test = ["-module(",ModName,"). ",Test0], - ?line Opts = case WriteBeam of - dont_write_beam -> - [binary,return_errors|Warnings]; - write_beam -> - [return_errors|Warnings] - end, - ?line ok = file:write_file(File, Test), + Opts = case WriteBeam of + dont_write_beam -> + [binary,return_errors|Warnings]; + write_beam -> + [return_errors|Warnings] + end, + ok = file:write_file(File, Test), %% Compile once just to print all errors and warnings. - ?line compile:file(File, [binary,report|Warnings]), + compile:file(File, [binary,report|Warnings]), %% Test result of compilation. io:format("~p\n", [Opts]), - ?line Res = case compile:file(File, Opts) of - {ok,Mod,_,[{_File,Ws}]} -> - %io:format("compile:file(~s,~p) ->~n~p~n", - % [File,Opts,Ws]), - {warning,Ws}; - {ok,Mod,_,[]} -> - %io:format("compile:file(~s,~p) ->~n~p~n", - % [File,Opts,Ws]), - []; - {ok,Mod,[{_File,Ws}]} -> - {warning,Ws}; - {ok,Mod,[]} -> - []; - {error,[{XFile,Es}],Ws} = _ZZ when is_list(XFile) -> - %io:format("compile:file(~s,~p) ->~n~p~n", - % [File,Opts,_ZZ]), - {error,Es,Ws}; - {error,[{XFile,Es1},{XFile,Es2}],Ws} = _ZZ - when is_list(XFile) -> - %io:format("compile:file(~s,~p) ->~n~p~n", - % [File,Opts,_ZZ]), - {error,Es1++Es2,Ws}; - {error,Es,[{_File,Ws}]} = _ZZ-> - %io:format("compile:file(~s,~p) ->~n~p~n", - % [File,Opts,_ZZ]), - {error,Es,Ws} - end, + Res = case compile:file(File, Opts) of + {ok,Mod,_,[{_File,Ws}]} -> + {warning,Ws}; + {ok,Mod,_,[]} -> + []; + {ok,Mod,[{_File,Ws}]} -> + {warning,Ws}; + {ok,Mod,[]} -> + []; + {error,[{XFile,Es}],Ws} = _ZZ when is_list(XFile) -> + {error,Es,Ws}; + {error,[{XFile,Es1},{XFile,Es2}],Ws} = _ZZ + when is_list(XFile) -> + {error,Es1++Es2,Ws}; + {error,Es,[{_File,Ws}]} = _ZZ-> + {error,Es,Ws} + end, file:delete(File), Res. fail() -> - io:format("failed~n"), - ?t:fail(). + ct:fail(failed). diff --git a/lib/compiler/test/float_SUITE.erl b/lib/compiler/test/float_SUITE.erl index 1b313ad021..771016812b 100644 --- a/lib/compiler/test/float_SUITE.erl +++ b/lib/compiler/test/float_SUITE.erl @@ -22,7 +22,7 @@ init_per_group/2,end_per_group/2, pending/1,bif_calls/1,math_functions/1,mixed_float_and_int/1]). --include_lib("test_server/include/test_server.hrl"). +-include_lib("common_test/include/ct.hrl"). suite() -> [{ct_hooks,[ts_install_cth]}]. @@ -51,11 +51,11 @@ end_per_group(_GroupName, Config) -> %% Shows the effect of pending exceptions on the x86. pending(Config) when is_list(Config) -> - ?line case catch float_mul(1, 1.1e300, 3.14e300) of - {'EXIT',{badarith,_}} -> ok; - Other -> ?t:fail({expected_exception,Other}) - end, - ?line 0.0 = float_sub(2.0). + case catch float_mul(1, 1.1e300, 3.14e300) of + {'EXIT',{badarith,_}} -> ok; + Other -> ct:fail({expected_exception,Other}) + end, + 0.0 = float_sub(2.0). float_sub(A)-> catch A - 2.0. @@ -69,11 +69,11 @@ float_mul(Iter, A, B) when is_float(A), is_float(B) -> %% Thanks to Mikael Pettersson and Tobias Lindahl (HiPE). bif_calls(Config) when is_list(Config) -> - ?line {'EXIT',{badarith,_}} = (catch bad_arith(2.0, 1.7)), - ?line {'EXIT',{badarith,_}} = (catch bad_arith_again(2.0, [])), - ?line {'EXIT',{badarith,_}} = (catch bad_arith_xor(2.0, [])), - ?line {'EXIT',{badarith,_}} = (catch bad_arith_hd(2.0, [])), - ?line {'EXIT',{badarith,_}} = (catch bad_negate(2.0, 1.7)), + {'EXIT',{badarith,_}} = (catch bad_arith(2.0, 1.7)), + {'EXIT',{badarith,_}} = (catch bad_arith_again(2.0, [])), + {'EXIT',{badarith,_}} = (catch bad_arith_xor(2.0, [])), + {'EXIT',{badarith,_}} = (catch bad_arith_hd(2.0, [])), + {'EXIT',{badarith,_}} = (catch bad_negate(2.0, 1.7)), ok. bad_arith(X, Y) when is_float(X) -> @@ -114,51 +114,51 @@ bad_negate(X, Y) when is_float(X) -> math_functions(Config) when is_list(Config) -> %% Mostly silly coverage. - ?line 0.0 = math:tan(0), - ?line 0.0 = math:atan2(0, 1), - ?line 0.0 = math:sinh(0), - ?line 1.0 = math:cosh(0), - ?line 0.0 = math:tanh(0), + 0.0 = math:tan(0), + 0.0 = math:atan2(0, 1), + 0.0 = math:sinh(0), + 1.0 = math:cosh(0), + 0.0 = math:tanh(0), 1.0 = math:log2(2), - ?line 1.0 = math:log10(10), - ?line -1.0 = math:cos(math:pi()), - ?line 1.0 = math:exp(0), - ?line 1.0 = math:pow(math:pi(), 0), - ?line 0.0 = math:log(1), - ?line 0.0 = math:asin(0), - ?line 0.0 = math:acos(1), - ?line ?OPTIONAL(0.0, math:asinh(0)), - ?line ?OPTIONAL(0.0, math:acosh(1)), - ?line ?OPTIONAL(0.0, math:atanh(0)), - ?line ?OPTIONAL(0.0, math:erf(0)), - ?line ?OPTIONAL(1.0, math:erfc(0)), - - ?line 0.0 = math:tan(id(0)), - ?line 0.0 = math:atan2(id(0), 1), - ?line 0.0 = math:sinh(id(0)), - ?line 1.0 = math:cosh(id(0)), - ?line 0.0 = math:tanh(id(0)), + 1.0 = math:log10(10), + -1.0 = math:cos(math:pi()), + 1.0 = math:exp(0), + 1.0 = math:pow(math:pi(), 0), + 0.0 = math:log(1), + 0.0 = math:asin(0), + 0.0 = math:acos(1), + ?OPTIONAL(0.0, math:asinh(0)), + ?OPTIONAL(0.0, math:acosh(1)), + ?OPTIONAL(0.0, math:atanh(0)), + ?OPTIONAL(0.0, math:erf(0)), + ?OPTIONAL(1.0, math:erfc(0)), + + 0.0 = math:tan(id(0)), + 0.0 = math:atan2(id(0), 1), + 0.0 = math:sinh(id(0)), + 1.0 = math:cosh(id(0)), + 0.0 = math:tanh(id(0)), 1.0 = math:log2(id(2)), - ?line 1.0 = math:log10(id(10)), - ?line 1.0 = math:exp(id(0)), - ?line 0.0 = math:log(id(1)), - ?line 0.0 = math:asin(id(0)), - ?line 0.0 = math:acos(id(1)), - ?line ?OPTIONAL(0.0, math:asinh(id(0))), - ?line ?OPTIONAL(0.0, math:acosh(id(1))), - ?line ?OPTIONAL(0.0, math:atanh(id(0))), - ?line ?OPTIONAL(0.0, math:erf(id(0))), - ?line ?OPTIONAL(1.0, math:erfc(id(0))), + 1.0 = math:log10(id(10)), + 1.0 = math:exp(id(0)), + 0.0 = math:log(id(1)), + 0.0 = math:asin(id(0)), + 0.0 = math:acos(id(1)), + ?OPTIONAL(0.0, math:asinh(id(0))), + ?OPTIONAL(0.0, math:acosh(id(1))), + ?OPTIONAL(0.0, math:atanh(id(0))), + ?OPTIONAL(0.0, math:erf(id(0))), + ?OPTIONAL(1.0, math:erfc(id(0))), %% Only for coverage (of beam_type.erl). - ?line {'EXIT',{undef,_}} = (catch math:fnurfla(0)), - ?line {'EXIT',{undef,_}} = (catch math:fnurfla(0, 0)), - ?line {'EXIT',{badarg,_}} = (catch float(kalle)), - ?line {'EXIT',{badarith,_}} = (catch name/1), + {'EXIT',{undef,_}} = (catch math:fnurfla(0)), + {'EXIT',{undef,_}} = (catch math:fnurfla(0, 0)), + {'EXIT',{badarg,_}} = (catch float(kalle)), + {'EXIT',{badarith,_}} = (catch name/1), ok. mixed_float_and_int(Config) when is_list(Config) -> - ?line 129.0 = pc(77, 23, 5), + 129.0 = pc(77, 23, 5), ok. pc(Cov, NotCov, X) -> diff --git a/lib/compiler/test/fun_SUITE.erl b/lib/compiler/test/fun_SUITE.erl index 36a4d6fce2..77559ae2e6 100644 --- a/lib/compiler/test/fun_SUITE.erl +++ b/lib/compiler/test/fun_SUITE.erl @@ -27,7 +27,7 @@ %% Internal exports. -export([call_me/1,dup1/0,dup2/0]). --include_lib("test_server/include/test_server.hrl"). +-include_lib("common_test/include/ct.hrl"). suite() -> [{ct_hooks,[ts_install_cth]}]. @@ -60,9 +60,8 @@ l1() -> ?T((begin G = fun(1=0) -> ok end, {'EXIT',_} = (catch G(2)), ok end), ok) ]. -test1(suite) -> []; test1(Config) when is_list(Config) -> - ?line lists:foreach(fun one_test/1, eval_list(l1(), [])), + lists:foreach(fun one_test/1, eval_list(l1(), [])), ok. evaluate(Str, Vars) -> @@ -93,7 +92,7 @@ one_test({C, E, Str, Correct}) -> true -> io:format("ERROR: Compiled: ~p. Expected ~p. Got ~p.~n", [Str, Correct, C]), - test_server:fail(comp) + ct:fail(comp) end, if E == Correct -> @@ -101,7 +100,7 @@ one_test({C, E, Str, Correct}) -> true -> io:format("ERROR: Interpreted: ~p. Expected ~p. Got ~p.~n", [Str, Correct, E]), - test_server:fail(comp) + ct:fail(comp) end. -record(b, {c}). @@ -109,9 +108,9 @@ one_test({C, E, Str, Correct}) -> %% OTP-7102. (Thanks to Simon Cornish.) overwritten_fun(Config) when is_list(Config) -> - ?line {a2,a} = overwritten_fun_1(a), - ?line {a2,{b,c}} = overwritten_fun_1(#b{c=c}), - ?line one = overwritten_fun_1(#b{c=[]}), + {a2,a} = overwritten_fun_1(a), + {a2,{b,c}} = overwritten_fun_1(#b{c=c}), + one = overwritten_fun_1(#b{c=[]}), ok. overwritten_fun_1(A) -> @@ -153,8 +152,8 @@ otp_7202_func() -> no_value. bif_fun(Config) when is_list(Config) -> - ?line F = fun abs/1, - ?line 5 = F(-5), + F = fun abs/1, + 5 = F(-5), ok. -define(APPLY(M, F, A), (fun(Fun) -> {ok,{a,b}} = Fun({a,b}) end)(fun M:F/A)). diff --git a/lib/compiler/test/guard_SUITE.erl b/lib/compiler/test/guard_SUITE.erl index 47eb1ba78b..129db039e1 100644 --- a/lib/compiler/test/guard_SUITE.erl +++ b/lib/compiler/test/guard_SUITE.erl @@ -19,7 +19,7 @@ %% -module(guard_SUITE). --include_lib("test_server/include/test_server.hrl"). +-include_lib("common_test/include/ct.hrl"). -export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, init_per_group/2,end_per_group/2, @@ -69,23 +69,23 @@ end_per_group(_GroupName, Config) -> misc(Config) when is_list(Config) -> - ?line 42 = case id(42) of - X when -X -> ok; - X -> X - end, - ?line {a,b,c} = misc_1([{{a,b,c}},{[4]},{[3]},{-2}]), - ?line none = misc_1([{{a,b,c}},{[4]},{[3]},{-3}]), - ?line none = misc_1([{{a,b,c}},{[4]},{[7]},{-2}]), - ?line none = misc_1([{{a,b,c}},{[4]},{[3]},{[1,2,3]}]), - - ?line {ok,buf,<<>>} = get_data({o,true,raw}, 0, buf), - ?line {ok,buf,<<>>} = get_data({o,true,raw}, 42, buf), - ?line {ok,buf,<<>>} = get_data({o,false,raw}, 0, buf), - ?line error = get_data({o,false,raw}, 42, buf), - ?line {ok,buf,<<>>} = get_data({o,true,0}, 0, buf), - ?line {ok,buf,<<>>} = get_data({o,true,0}, 42, buf), - ?line {ok,buf,<<>>} = get_data({o,false,0}, 0, buf), - ?line error = get_data({o,false,0}, 42, buf), + 42 = case id(42) of + X when -X -> ok; + X -> X + end, + {a,b,c} = misc_1([{{a,b,c}},{[4]},{[3]},{-2}]), + none = misc_1([{{a,b,c}},{[4]},{[3]},{-3}]), + none = misc_1([{{a,b,c}},{[4]},{[7]},{-2}]), + none = misc_1([{{a,b,c}},{[4]},{[3]},{[1,2,3]}]), + + {ok,buf,<<>>} = get_data({o,true,raw}, 0, buf), + {ok,buf,<<>>} = get_data({o,true,raw}, 42, buf), + {ok,buf,<<>>} = get_data({o,false,raw}, 0, buf), + error = get_data({o,false,raw}, 42, buf), + {ok,buf,<<>>} = get_data({o,true,0}, 0, buf), + {ok,buf,<<>>} = get_data({o,true,0}, 42, buf), + {ok,buf,<<>>} = get_data({o,false,0}, 0, buf), + error = get_data({o,false,0}, 42, buf), ok. @@ -107,11 +107,11 @@ get_data({o,Active,Raw}, BytesToRead, Buffer) end. const_cond(Config) when is_list(Config) -> - ?line ok = const_cond({}, 0), - ?line ok = const_cond({a}, 1), - ?line error = const_cond({a,b}, 3), - ?line error = const_cond({a}, 0), - ?line error = const_cond({a,b}, 1), + ok = const_cond({}, 0), + ok = const_cond({a}, 1), + error = const_cond({a,b}, 3), + error = const_cond({a}, 0), + error = const_cond({a,b}, 1), ok. const_cond(T, Sz) -> @@ -132,80 +132,80 @@ basic_not(Config) when is_list(Config) -> D = id(5), ATuple = {False,True,Glurf}, - ?line check(fun() -> if not false -> ok; true -> error end end, ok), - ?line check(fun() -> if not true -> ok; true -> error end end, error), - ?line check(fun() -> if not False -> ok; true -> error end end, ok), - ?line check(fun() -> if not True -> ok; true -> error end end, error), + check(fun() -> if not false -> ok; true -> error end end, ok), + check(fun() -> if not true -> ok; true -> error end end, error), + check(fun() -> if not False -> ok; true -> error end end, ok), + check(fun() -> if not True -> ok; true -> error end end, error), - ?line check(fun() -> if A > B -> gt; A < B -> lt; A == B -> eq end end, lt), - ?line check(fun() -> if A > C -> gt; A < C -> lt; A == C -> eq end end, gt), - ?line check(fun() -> if A > D -> gt; A < D -> lt; A == D -> eq end end, eq), + check(fun() -> if A > B -> gt; A < B -> lt; A == B -> eq end end, lt), + check(fun() -> if A > C -> gt; A < C -> lt; A == C -> eq end end, gt), + check(fun() -> if A > D -> gt; A < D -> lt; A == D -> eq end end, eq), - ?line check(fun() -> if not (7 > 453) -> le; not (7 < 453) -> ge; - not (7 == 453) -> ne; true -> eq end end, le), - ?line check(fun() -> if not (7 > -8) -> le; not (7 < -8) -> ge; - not (7 == -8) -> ne; true -> eq end end, ge), - ?line check(fun() -> if not (7 > 7) -> le; not (7 < 7) -> ge; - not (7 == 7) -> ne; true -> eq end end, le), + check(fun() -> if not (7 > 453) -> le; not (7 < 453) -> ge; + not (7 == 453) -> ne; true -> eq end end, le), + check(fun() -> if not (7 > -8) -> le; not (7 < -8) -> ge; + not (7 == -8) -> ne; true -> eq end end, ge), + check(fun() -> if not (7 > 7) -> le; not (7 < 7) -> ge; + not (7 == 7) -> ne; true -> eq end end, le), - ?line check(fun() -> if not (A > B) -> le; not (A < B) -> ge; - not (A == B) -> ne; true -> eq end end, le), - ?line check(fun() -> if not (A > C) -> le; not (A < C) -> ge; - not (A == C) -> ne; true -> eq end end, ge), - ?line check(fun() -> if not (A > D) -> le; not (A < D) -> ge; - not (A == D) -> ne; true -> eq end end, le), + check(fun() -> if not (A > B) -> le; not (A < B) -> ge; + not (A == B) -> ne; true -> eq end end, le), + check(fun() -> if not (A > C) -> le; not (A < C) -> ge; + not (A == C) -> ne; true -> eq end end, ge), + check(fun() -> if not (A > D) -> le; not (A < D) -> ge; + not (A == D) -> ne; true -> eq end end, le), - ?line check(fun() -> if not element(1, ATuple) -> ok; true -> error end end, ok), - ?line check(fun() -> if not element(2, ATuple) -> ok; true -> error end end, error), - ?line check(fun() -> if not element(3, ATuple) -> ok; true -> error end end, error), + check(fun() -> if not element(1, ATuple) -> ok; true -> error end end, ok), + check(fun() -> if not element(2, ATuple) -> ok; true -> error end end, error), + check(fun() -> if not element(3, ATuple) -> ok; true -> error end end, error), - ?line check(fun() -> if not glurf -> ok; true -> error end end, error), - ?line check(fun() -> if not Glurf -> ok; true -> error end end, error), + check(fun() -> if not glurf -> ok; true -> error end end, error), + check(fun() -> if not Glurf -> ok; true -> error end end, error), ok. complex_not(Config) when is_list(Config) -> ATuple = id({false,true,gurka}), - ?line check(fun() -> if not(element(1, ATuple)) -> ok; true -> error end end, ok), - ?line check(fun() -> if not(element(2, ATuple)) -> ok; true -> error end end, error), + check(fun() -> if not(element(1, ATuple)) -> ok; true -> error end end, ok), + check(fun() -> if not(element(2, ATuple)) -> ok; true -> error end end, error), - ?line check(fun() -> if not(element(3, ATuple) == gurka) -> ok; - true -> error end end, error), - ?line check(fun() -> if not(element(3, ATuple) =/= gurka) -> ok; - true -> error end end, ok), + check(fun() -> if not(element(3, ATuple) == gurka) -> ok; + true -> error end end, error), + check(fun() -> if not(element(3, ATuple) =/= gurka) -> ok; + true -> error end end, ok), - ?line check(fun() -> if {a,not(element(2, ATuple))} == {a,false} -> ok; - true -> error end end, ok), - ?line check(fun() -> if {a,not(element(1, ATuple))} == {a,false} -> ok; - true -> error end end, error), + check(fun() -> if {a,not(element(2, ATuple))} == {a,false} -> ok; + true -> error end end, ok), + check(fun() -> if {a,not(element(1, ATuple))} == {a,false} -> ok; + true -> error end end, error), - ?line check(fun() -> if not(element(1, ATuple) or element(3, ATuple)) -> ok; - true -> error end end, error), + check(fun() -> if not(element(1, ATuple) or element(3, ATuple)) -> ok; + true -> error end end, error), %% orelse - ?line check(fun() -> if not(element(1, ATuple) orelse element(3, ATuple)) -> ok; - true -> error end end, error), + check(fun() -> if not(element(1, ATuple) orelse element(3, ATuple)) -> ok; + true -> error end end, error), ok. nested_nots(Config) when is_list(Config) -> - ?line true = nested_not_1(0, 0), - ?line true = nested_not_1(0, 1), - ?line true = nested_not_1(a, b), - ?line true = nested_not_1(10, 0), - ?line false = nested_not_1(z, a), - ?line false = nested_not_1(3.4, {anything,goes}), - ?line false = nested_not_1(3.4, atom), - ?line true = nested_not_1(3.0, [list]), - - ?line true = nested_not_2(false, false, 42), - ?line true = nested_not_2(false, true, 42), - ?line true = nested_not_2(true, false, 42), - ?line true = nested_not_2(true, true, 42), - ?line true = nested_not_2(false, false, atom), - ?line false = nested_not_2(false, true, atom), - ?line false = nested_not_2(true, false, atom), - ?line false = nested_not_2(true, true, atom), + true = nested_not_1(0, 0), + true = nested_not_1(0, 1), + true = nested_not_1(a, b), + true = nested_not_1(10, 0), + false = nested_not_1(z, a), + false = nested_not_1(3.4, {anything,goes}), + false = nested_not_1(3.4, atom), + true = nested_not_1(3.0, [list]), + + true = nested_not_2(false, false, 42), + true = nested_not_2(false, true, 42), + true = nested_not_2(true, false, 42), + true = nested_not_2(true, true, 42), + true = nested_not_2(false, false, atom), + false = nested_not_2(false, true, atom), + false = nested_not_2(true, false, atom), + false = nested_not_2(true, true, atom), ok. nested_not_1(X, Y) when not (((X>Y) or not(is_atom(X))) and @@ -227,112 +227,112 @@ semicolon(Config) when is_list(Config) -> %% True/false combined using ';' (literal atoms). - ?line check(fun() -> if true; false -> ok end end, ok), - ?line check(fun() -> if false; true -> ok end end, ok), - ?line check(fun() -> if true; true -> ok end end, ok), - ?line check(fun() -> if false; false -> ok; true -> error end end, error), - ?line check(fun() -> - {'EXIT',{if_clause,_}} = (catch if false; false -> ok end), - exit - end, exit), + check(fun() -> if true; false -> ok end end, ok), + check(fun() -> if false; true -> ok end end, ok), + check(fun() -> if true; true -> ok end end, ok), + check(fun() -> if false; false -> ok; true -> error end end, error), + check(fun() -> + {'EXIT',{if_clause,_}} = (catch if false; false -> ok end), + exit + end, exit), %% True/false combined used ';'. True = id(true), False = id(false), - ?line check(fun() -> if True; False -> ok end end, ok), - ?line check(fun() -> if False; True -> ok end end, ok), - ?line check(fun() -> if True; True -> ok end end, ok), - ?line check(fun() -> if False; False -> ok; true -> error end end, error), - ?line check(fun() -> - {'EXIT',{if_clause,_}} = (catch if False; False -> ok end), - exit - end, exit), + check(fun() -> if True; False -> ok end end, ok), + check(fun() -> if False; True -> ok end end, ok), + check(fun() -> if True; True -> ok end end, ok), + check(fun() -> if False; False -> ok; true -> error end end, error), + check(fun() -> + {'EXIT',{if_clause,_}} = (catch if False; False -> ok end), + exit + end, exit), %% Combine true/false with a non-boolean value. Glurf = id(glurf), - ?line check(fun() -> if True; Glurf -> ok end end, ok), - ?line check(fun() -> if Glurf; True -> ok end end, ok), - ?line check(fun() -> if Glurf; Glurf -> ok; true -> error end end, error), - ?line check(fun() -> if False; Glurf -> ok; true -> error end end, error), - ?line check(fun() -> if Glurf; False -> ok; true -> error end end, error), - ?line check(fun() -> - {'EXIT',{if_clause,_}} = (catch if Glurf; Glurf -> ok end), - exit - end, exit), + check(fun() -> if True; Glurf -> ok end end, ok), + check(fun() -> if Glurf; True -> ok end end, ok), + check(fun() -> if Glurf; Glurf -> ok; true -> error end end, error), + check(fun() -> if False; Glurf -> ok; true -> error end end, error), + check(fun() -> if Glurf; False -> ok; true -> error end end, error), + check(fun() -> + {'EXIT',{if_clause,_}} = (catch if Glurf; Glurf -> ok end), + exit + end, exit), %% Combine true/false with errors. ATuple = id({false,true,gurka}), - ?line check(fun() -> if True; element(42, ATuple) -> ok end end, ok), - ?line check(fun() -> if element(42, ATuple); True -> ok end end, ok), - ?line check(fun() -> if element(42, ATuple); element(42, ATuple) -> ok; - true -> error end end, error), - ?line check(fun() -> if False; element(42, ATuple) -> ok; - true -> error end end, error), - ?line check(fun() -> if element(42, ATuple); - False -> ok; true -> error end end, error), - ?line check(fun() -> - {'EXIT',{if_clause,_}} = - (catch if element(42, ATuple); - element(42, ATuple) -> ok end), - exit - end, exit), + check(fun() -> if True; element(42, ATuple) -> ok end end, ok), + check(fun() -> if element(42, ATuple); True -> ok end end, ok), + check(fun() -> if element(42, ATuple); element(42, ATuple) -> ok; + true -> error end end, error), + check(fun() -> if False; element(42, ATuple) -> ok; + true -> error end end, error), + check(fun() -> if element(42, ATuple); + False -> ok; true -> error end end, error), + check(fun() -> + {'EXIT',{if_clause,_}} = + (catch if element(42, ATuple); + element(42, ATuple) -> ok end), + exit + end, exit), ok. complex_semicolon(Config) when is_list(Config) -> - ?line ok = csemi1(int, {blurf}), - ?line ok = csemi1(string, {blurf}), - ?line ok = csemi1(float, [a]), - ?line error = csemi1(35, 42), + ok = csemi1(int, {blurf}), + ok = csemi1(string, {blurf}), + ok = csemi1(float, [a]), + error = csemi1(35, 42), %% 2 - ?line ok = csemi2({}, {a,b,c}), - ?line ok = csemi2({1,3.5}, {a,b,c}), - ?line ok = csemi2(dum, {a,b,c}), + ok = csemi2({}, {a,b,c}), + ok = csemi2({1,3.5}, {a,b,c}), + ok = csemi2(dum, {a,b,c}), - ?line ok = csemi2({45,-19.3}, {}), - ?line ok = csemi2({45,-19.3}, {dum}), - ?line ok = csemi2({45,-19.3}, {dum,dum}), + ok = csemi2({45,-19.3}, {}), + ok = csemi2({45,-19.3}, {dum}), + ok = csemi2({45,-19.3}, {dum,dum}), - ?line error = csemi2({45}, {dum}), - ?line error = csemi2([], {dum}), - ?line error = csemi2({dum}, []), - ?line error = csemi2([], []), + error = csemi2({45}, {dum}), + error = csemi2([], {dum}), + error = csemi2({dum}, []), + error = csemi2([], []), %% 3 - ?line csemi3(fun csemi3a/4), - ?line csemi3(fun csemi3b/4), - ?line csemi3(fun csemi3c/4), + csemi3(fun csemi3a/4), + csemi3(fun csemi3b/4), + csemi3(fun csemi3c/4), %% 4 - ?line csemi4(fun csemi4a/4), - ?line csemi4(fun csemi4b/4), - ?line csemi4(fun csemi4c/4), - ?line csemi4(fun csemi4d/4), + csemi4(fun csemi4a/4), + csemi4(fun csemi4b/4), + csemi4(fun csemi4c/4), + csemi4(fun csemi4d/4), %% 4, 'orelse' instead of 'or' - ?line csemi4_orelse(fun csemi4_orelse_a/4), - ?line csemi4_orelse(fun csemi4_orelse_b/4), - ?line csemi4_orelse(fun csemi4_orelse_c/4), - ?line csemi4_orelse(fun csemi4_orelse_d/4), + csemi4_orelse(fun csemi4_orelse_a/4), + csemi4_orelse(fun csemi4_orelse_b/4), + csemi4_orelse(fun csemi4_orelse_c/4), + csemi4_orelse(fun csemi4_orelse_d/4), %% 5 - ?line error = csemi5(0, 0), - ?line ok = csemi5(5, 0), - ?line ok = csemi5(4, -4), - ?line ok = csemi5(10, -4), + error = csemi5(0, 0), + ok = csemi5(5, 0), + ok = csemi5(4, -4), + ok = csemi5(10, -4), %% 6 - ?line error = csemi6({a}, 0), - ?line ok = csemi6({a,b}, 0), - ?line ok = csemi6({}, 3), - ?line ok = csemi6({a,b,c}, 3), + error = csemi6({a}, 0), + ok = csemi6({a,b}, 0), + ok = csemi6({}, 3), + ok = csemi6({a,b,c}, 3), %% 7 error = csemi7(#{a=>1}, 1, 0), @@ -427,7 +427,7 @@ csemi4_orelse(Test) -> ok = Test({}, 2, blurf, 0), ok = Test({}, 2, {1}, 2), - ?line error = Test([], 1, {}, 0), + error = Test([], 1, {}, 0), ok. @@ -460,72 +460,72 @@ comma(Config) when is_list(Config) -> %% ',' combinations of literal true/false. - ?line check(fun() -> if true, false -> ok; true -> error end end, error), - ?line check(fun() -> if false, true -> ok; true -> error end end, error), - ?line check(fun() -> if true, true -> ok end end, ok), - ?line check(fun() -> if false, false -> ok; true -> error end end, error), - ?line check(fun() -> - {'EXIT',{if_clause,_}} = - (catch if true, false -> ok; - false, true -> ok; - false, false -> ok - end), - exit - end, exit), + check(fun() -> if true, false -> ok; true -> error end end, error), + check(fun() -> if false, true -> ok; true -> error end end, error), + check(fun() -> if true, true -> ok end end, ok), + check(fun() -> if false, false -> ok; true -> error end end, error), + check(fun() -> + {'EXIT',{if_clause,_}} = + (catch if true, false -> ok; + false, true -> ok; + false, false -> ok + end), + exit + end, exit), %% ',' combinations of true/false in variables. True = id(true), False = id(false), - ?line check(fun() -> if True, False -> ok; true -> error end end, error), - ?line check(fun() -> if False, True -> ok; true -> error end end, error), - ?line check(fun() -> if True, True -> ok end end, ok), - ?line check(fun() -> if False, False -> ok; true -> error end end, error), - ?line check(fun() -> - {'EXIT',{if_clause,_}} = - (catch if True, False -> ok; - False, True -> ok; - False, False -> ok - end), - exit - end, exit), + check(fun() -> if True, False -> ok; true -> error end end, error), + check(fun() -> if False, True -> ok; true -> error end end, error), + check(fun() -> if True, True -> ok end end, ok), + check(fun() -> if False, False -> ok; true -> error end end, error), + check(fun() -> + {'EXIT',{if_clause,_}} = + (catch if True, False -> ok; + False, True -> ok; + False, False -> ok + end), + exit + end, exit), %% ',' combinations of true/false, and non-boolean in variables. Glurf = id(glurf), - ?line check(fun() -> if True, Glurf -> ok; true -> error end end, error), - ?line check(fun() -> if Glurf, True -> ok; true -> error end end, error), - ?line check(fun() -> if True, True -> ok end end, ok), - ?line check(fun() -> if Glurf, Glurf -> ok; true -> error end end, error), - ?line check(fun() -> - {'EXIT',{if_clause,_}} = - (catch if True, Glurf -> ok; - Glurf, True -> ok; - Glurf, Glurf -> ok - end), - exit - end, exit), + check(fun() -> if True, Glurf -> ok; true -> error end end, error), + check(fun() -> if Glurf, True -> ok; true -> error end end, error), + check(fun() -> if True, True -> ok end end, ok), + check(fun() -> if Glurf, Glurf -> ok; true -> error end end, error), + check(fun() -> + {'EXIT',{if_clause,_}} = + (catch if True, Glurf -> ok; + Glurf, True -> ok; + Glurf, Glurf -> ok + end), + exit + end, exit), %% ',' combinations of true/false with errors. ATuple = id({a,b,c}), - ?line check(fun() -> if True, element(42, ATuple) -> ok; - true -> error end end, error), - ?line check(fun() -> if element(42, ATuple), True -> ok; - true -> error end end, error), - ?line check(fun() -> if True, True -> ok end end, ok), - ?line check(fun() -> if element(42, ATuple), element(42, ATuple) -> ok; - true -> error end end, error), - ?line check(fun() -> - {'EXIT',{if_clause,_}} = - (catch if True, element(42, ATuple) -> ok; - element(42, ATuple), True -> ok; - element(42, ATuple), element(42, ATuple) -> ok - end), - exit - end, exit), + check(fun() -> if True, element(42, ATuple) -> ok; + true -> error end end, error), + check(fun() -> if element(42, ATuple), True -> ok; + true -> error end end, error), + check(fun() -> if True, True -> ok end end, ok), + check(fun() -> if element(42, ATuple), element(42, ATuple) -> ok; + true -> error end end, error), + check(fun() -> + {'EXIT',{if_clause,_}} = + (catch if True, element(42, ATuple) -> ok; + element(42, ATuple), True -> ok; + element(42, ATuple), element(42, ATuple) -> ok + end), + exit + end, exit), ok. @@ -535,35 +535,35 @@ or_guard(Config) when is_list(Config) -> Glurf = id(glurf), %% 'or' combinations of literal true/false. - ?line check(fun() -> if true or false -> ok end end, ok), - ?line check(fun() -> if false or true -> ok end end, ok), - ?line check(fun() -> if true or true -> ok end end, ok), - ?line check(fun() -> if false or false -> ok; true -> error end end, error), + check(fun() -> if true or false -> ok end end, ok), + check(fun() -> if false or true -> ok end end, ok), + check(fun() -> if true or true -> ok end end, ok), + check(fun() -> if false or false -> ok; true -> error end end, error), - ?line check(fun() -> if glurf or true -> ok; true -> error end end, error), - ?line check(fun() -> if true or glurf -> ok; true -> error end end, error), - ?line check(fun() -> if glurf or glurf -> ok; true -> error end end, error), + check(fun() -> if glurf or true -> ok; true -> error end end, error), + check(fun() -> if true or glurf -> ok; true -> error end end, error), + check(fun() -> if glurf or glurf -> ok; true -> error end end, error), - ?line check(fun() -> - {'EXIT',{if_clause,_}} = (catch if false or false -> ok end), - exit - end, exit), + check(fun() -> + {'EXIT',{if_clause,_}} = (catch if false or false -> ok end), + exit + end, exit), %% 'or' combinations using variables containing true/false. - ?line check(fun() -> if True or False -> ok end end, ok), - ?line check(fun() -> if False or True -> ok end end, ok), - ?line check(fun() -> if True or True -> ok end end, ok), - ?line check(fun() -> if False or False -> ok; true -> error end end, error), + check(fun() -> if True or False -> ok end end, ok), + check(fun() -> if False or True -> ok end end, ok), + check(fun() -> if True or True -> ok end end, ok), + check(fun() -> if False or False -> ok; true -> error end end, error), - ?line check(fun() -> if True or Glurf -> ok; true -> error end end, error), - ?line check(fun() -> if Glurf or True -> ok; true -> error end end, error), - ?line check(fun() -> if Glurf or Glurf -> ok; true -> error end end, error), + check(fun() -> if True or Glurf -> ok; true -> error end end, error), + check(fun() -> if Glurf or True -> ok; true -> error end end, error), + check(fun() -> if Glurf or Glurf -> ok; true -> error end end, error), - ?line check(fun() -> - {'EXIT',{if_clause,_}} = (catch if False or False -> ok end), - exit - end, exit), + check(fun() -> + {'EXIT',{if_clause,_}} = (catch if False or False -> ok end), + exit + end, exit), ok. @@ -572,142 +572,142 @@ more_or_guards(Config) when is_list(Config) -> False = id(false), ATuple = id({false,true,gurka}), - ?line check(fun() -> - if element(42, ATuple) or False -> ok; - true -> error end - end, error), - - ?line check(fun() -> - if False or element(42, ATuple) -> ok; - true -> error end - end, error), - - ?line check(fun() -> - if element(18, ATuple) or element(42, ATuple) -> ok; - true -> error end - end, error), - - ?line check(fun() -> - if True or element(42, ATuple) -> ok; - true -> error end - end, error), - - ?line check(fun() -> - if element(42, ATuple) or True -> ok; - true -> error end - end, error), - - ?line check(fun() -> - if element(1, ATuple) or element(42, ATuple) or True -> ok; - true -> error end - end, error), - - ?line check(fun() -> - if element(1, ATuple) or True or element(42, ATuple) -> ok; - true -> error end - end, error), - - ?line check(fun() -> - if - (<<False:8>> == <<0>>) or element(2, ATuple) -> ok; - true -> error end - end, error), - - ?line check(fun() -> - if - element(2, ATuple) or (<<True:8>> == <<1>>) -> ok; - true -> error end - end, error), - - ?line check(fun() -> - if element(2, ATuple) or element(42, ATuple) -> ok; - true -> error end - end, error), - - ?line check(fun() -> - if - element(1, ATuple) or - element(2, ATuple) or - element(19, ATuple) -> ok; - true -> error end - end, error), + check(fun() -> + if element(42, ATuple) or False -> ok; + true -> error end + end, error), + + check(fun() -> + if False or element(42, ATuple) -> ok; + true -> error end + end, error), + + check(fun() -> + if element(18, ATuple) or element(42, ATuple) -> ok; + true -> error end + end, error), + + check(fun() -> + if True or element(42, ATuple) -> ok; + true -> error end + end, error), + + check(fun() -> + if element(42, ATuple) or True -> ok; + true -> error end + end, error), + + check(fun() -> + if element(1, ATuple) or element(42, ATuple) or True -> ok; + true -> error end + end, error), + + check(fun() -> + if element(1, ATuple) or True or element(42, ATuple) -> ok; + true -> error end + end, error), + + check(fun() -> + if + (<<False:8>> == <<0>>) or element(2, ATuple) -> ok; + true -> error end + end, error), + + check(fun() -> + if + element(2, ATuple) or (<<True:8>> == <<1>>) -> ok; + true -> error end + end, error), + + check(fun() -> + if element(2, ATuple) or element(42, ATuple) -> ok; + true -> error end + end, error), + + check(fun() -> + if + element(1, ATuple) or + element(2, ATuple) or + element(19, ATuple) -> ok; + true -> error end + end, error), ok. complex_or_guards(Config) when is_list(Config) -> %% complex_or_1/2 - ?line ok = complex_or_1({a,b,c,d}, {1,2,3}), - ?line ok = complex_or_1({a,b,c,d}, {1}), - ?line ok = complex_or_1({a}, {1,2,3}), - ?line error = complex_or_1({a}, {1}), + ok = complex_or_1({a,b,c,d}, {1,2,3}), + ok = complex_or_1({a,b,c,d}, {1}), + ok = complex_or_1({a}, {1,2,3}), + error = complex_or_1({a}, {1}), - ?line error = complex_or_1(1, 2), - ?line error = complex_or_1([], {a,b,c,d}), - ?line error = complex_or_1({a,b,c,d}, []), + error = complex_or_1(1, 2), + error = complex_or_1([], {a,b,c,d}), + error = complex_or_1({a,b,c,d}, []), %% complex_or_2/1 - ?line ok = complex_or_2({true,{}}), - ?line ok = complex_or_2({false,{a}}), - ?line ok = complex_or_2({false,{a,b,c}}), - ?line ok = complex_or_2({true,{a,b,c,d}}), + ok = complex_or_2({true,{}}), + ok = complex_or_2({false,{a}}), + ok = complex_or_2({false,{a,b,c}}), + ok = complex_or_2({true,{a,b,c,d}}), - ?line error = complex_or_2({blurf,{a,b,c}}), + error = complex_or_2({blurf,{a,b,c}}), - ?line error = complex_or_2({true}), - ?line error = complex_or_2({true,no_tuple}), - ?line error = complex_or_2({true,[]}), + error = complex_or_2({true}), + error = complex_or_2({true,no_tuple}), + error = complex_or_2({true,[]}), %% complex_or_3/2 - ?line ok = complex_or_3({true}, {}), - ?line ok = complex_or_3({false}, {a}), - ?line ok = complex_or_3({false}, {a,b,c}), - ?line ok = complex_or_3({true}, {a,b,c,d}), - ?line ok = complex_or_3({false}, <<1,2,3>>), - ?line ok = complex_or_3({true}, <<1,2,3,4>>), + ok = complex_or_3({true}, {}), + ok = complex_or_3({false}, {a}), + ok = complex_or_3({false}, {a,b,c}), + ok = complex_or_3({true}, {a,b,c,d}), + ok = complex_or_3({false}, <<1,2,3>>), + ok = complex_or_3({true}, <<1,2,3,4>>), - ?line error = complex_or_3(blurf, {a,b,c}), + error = complex_or_3(blurf, {a,b,c}), - ?line error = complex_or_3({false}, <<1,2,3,4>>), - ?line error = complex_or_3([], <<1,2>>), - ?line error = complex_or_3({true}, 45), - ?line error = complex_or_3(<<>>, <<>>), + error = complex_or_3({false}, <<1,2,3,4>>), + error = complex_or_3([], <<1,2>>), + error = complex_or_3({true}, 45), + error = complex_or_3(<<>>, <<>>), %% complex_or_4/2 - ?line ok = complex_or_4(<<1,2,3>>, {true}), - ?line ok = complex_or_4(<<1,2,3>>, {false}), - ?line ok = complex_or_4(<<1,2,3>>, {true}), - ?line ok = complex_or_4({1,2,3}, {true}), - ?line error = complex_or_4({1,2,3,4}, {false}), + ok = complex_or_4(<<1,2,3>>, {true}), + ok = complex_or_4(<<1,2,3>>, {false}), + ok = complex_or_4(<<1,2,3>>, {true}), + ok = complex_or_4({1,2,3}, {true}), + error = complex_or_4({1,2,3,4}, {false}), - ?line error = complex_or_4(<<1,2,3,4>>, []), - ?line error = complex_or_4([], {true}), + error = complex_or_4(<<1,2,3,4>>, []), + error = complex_or_4([], {true}), %% complex_or_5/2 - ?line ok = complex_or_5(<<1>>, {false}), - ?line ok = complex_or_5(<<1,2,3>>, {true}), - ?line ok = complex_or_5(<<1,2,3,4>>, {false}), - ?line ok = complex_or_5({1,2,3}, {false}), - ?line ok = complex_or_5({1,2,3,4}, {false}), + ok = complex_or_5(<<1>>, {false}), + ok = complex_or_5(<<1,2,3>>, {true}), + ok = complex_or_5(<<1,2,3,4>>, {false}), + ok = complex_or_5({1,2,3}, {false}), + ok = complex_or_5({1,2,3,4}, {false}), - ?line error = complex_or_5(blurf, {false}), - ?line error = complex_or_5(<<1>>, klarf), - ?line error = complex_or_5(blurf, klarf), + error = complex_or_5(blurf, {false}), + error = complex_or_5(<<1>>, klarf), + error = complex_or_5(blurf, klarf), %% complex_or_6/2 - ?line ok = complex_or_6({true,true}, {1,2,3,4}), - ?line ok = complex_or_6({true,true}, <<1,2,3,4>>), - ?line ok = complex_or_6({false,false}, <<1,2,3,4>>), - ?line ok = complex_or_6({false,true}, <<1>>), - ?line ok = complex_or_6({true,false}, {1}), - ?line ok = complex_or_6({true,true}, {1}), + ok = complex_or_6({true,true}, {1,2,3,4}), + ok = complex_or_6({true,true}, <<1,2,3,4>>), + ok = complex_or_6({false,false}, <<1,2,3,4>>), + ok = complex_or_6({false,true}, <<1>>), + ok = complex_or_6({true,false}, {1}), + ok = complex_or_6({true,true}, {1}), - ?line error = complex_or_6({false,false}, {1}), + error = complex_or_6({false,false}, {1}), - ?line error = complex_or_6({true}, {1,2,3,4}), - ?line error = complex_or_6({}, {1,2,3,4}), - ?line error = complex_or_6([], {1,2,3,4}), - ?line error = complex_or_6([], {1,2,3,4}), - ?line error = complex_or_6({true,false}, klurf), + error = complex_or_6({true}, {1,2,3,4}), + error = complex_or_6({}, {1,2,3,4}), + error = complex_or_6([], {1,2,3,4}), + error = complex_or_6([], {1,2,3,4}), + error = complex_or_6({true,false}, klurf), ok. @@ -753,79 +753,79 @@ and_guard(Config) when is_list(Config) -> %% 'and' combinations of literal true/false. - ?line check(fun() -> if true and false -> ok; true -> error end end, error), - ?line check(fun() -> if false and true -> ok; true -> error end end, error), - ?line check(fun() -> if true and true -> ok end end, ok), - ?line check(fun() -> if false and false -> ok; true -> error end end, error), - - ?line check(fun() -> if glurf and true -> ok; true -> error end end, error), - ?line check(fun() -> if true and glurf -> ok; true -> error end end, error), - ?line check(fun() -> if glurf and glurf -> ok; true -> error end end, error), - - ?line check(fun() -> - {'EXIT',{if_clause,_}} = - (catch if true and false -> ok; - false and true -> ok; - false and false -> ok - end), - exit - end, exit), + check(fun() -> if true and false -> ok; true -> error end end, error), + check(fun() -> if false and true -> ok; true -> error end end, error), + check(fun() -> if true and true -> ok end end, ok), + check(fun() -> if false and false -> ok; true -> error end end, error), + + check(fun() -> if glurf and true -> ok; true -> error end end, error), + check(fun() -> if true and glurf -> ok; true -> error end end, error), + check(fun() -> if glurf and glurf -> ok; true -> error end end, error), + + check(fun() -> + {'EXIT',{if_clause,_}} = + (catch if true and false -> ok; + false and true -> ok; + false and false -> ok + end), + exit + end, exit), %% 'and' combinations of true/false in variables. True = id(true), False = id(false), - ?line check(fun() -> if True and False -> ok; true -> error end end, error), - ?line check(fun() -> if False and True -> ok; true -> error end end, error), - ?line check(fun() -> if True and True -> ok end end, ok), - ?line check(fun() -> if False and False -> ok; true -> error end end, error), - ?line check(fun() -> - {'EXIT',{if_clause,_}} = - (catch if True and False -> ok; - False and True -> ok; - False and False -> ok - end), - exit - end, exit), + check(fun() -> if True and False -> ok; true -> error end end, error), + check(fun() -> if False and True -> ok; true -> error end end, error), + check(fun() -> if True and True -> ok end end, ok), + check(fun() -> if False and False -> ok; true -> error end end, error), + check(fun() -> + {'EXIT',{if_clause,_}} = + (catch if True and False -> ok; + False and True -> ok; + False and False -> ok + end), + exit + end, exit), %% 'and' combinations of true/false and a non-boolean in variables. Glurf = id(glurf), - ?line check(fun() -> if True and Glurf -> ok; true -> error end end, error), - ?line check(fun() -> if Glurf and True -> ok; true -> error end end, error), - ?line check(fun() -> if True and True -> ok end end, ok), - ?line check(fun() -> if Glurf and Glurf -> ok; true -> error end end, error), - ?line check(fun() -> - {'EXIT',{if_clause,_}} = - (catch if True and Glurf -> ok; - Glurf and True -> ok; - Glurf and Glurf -> ok - end), - exit - end, exit), + check(fun() -> if True and Glurf -> ok; true -> error end end, error), + check(fun() -> if Glurf and True -> ok; true -> error end end, error), + check(fun() -> if True and True -> ok end end, ok), + check(fun() -> if Glurf and Glurf -> ok; true -> error end end, error), + check(fun() -> + {'EXIT',{if_clause,_}} = + (catch if True and Glurf -> ok; + Glurf and True -> ok; + Glurf and Glurf -> ok + end), + exit + end, exit), %% 'and' combinations of true/false with errors. ATuple = id({a,b,c}), - ?line check(fun() -> if True and element(42, ATuple) -> ok; - true -> error end end, error), - ?line check(fun() -> if element(42, ATuple) and True -> ok; - true -> error end end, error), - ?line check(fun() -> if True and True -> ok end end, ok), - ?line check(fun() -> if element(42, ATuple) and element(42, ATuple) -> ok; - true -> error end end, error), - ?line check(fun() -> - {'EXIT',{if_clause,_}} = - (catch if True and element(42, ATuple) -> ok; - element(42, ATuple) and True -> ok; - element(42, ATuple) and element(42, ATuple) -> ok - end), + check(fun() -> if True and element(42, ATuple) -> ok; + true -> error end end, error), + check(fun() -> if element(42, ATuple) and True -> ok; + true -> error end end, error), + check(fun() -> if True and True -> ok end end, ok), + check(fun() -> if element(42, ATuple) and element(42, ATuple) -> ok; + true -> error end end, error), + check(fun() -> + {'EXIT',{if_clause,_}} = + (catch if True and element(42, ATuple) -> ok; + element(42, ATuple) and True -> ok; + element(42, ATuple) and element(42, ATuple) -> ok + end), exit end, exit), - ?line ok = relprod({'Set',a,b}, {'Set',a,b}), + ok = relprod({'Set',a,b}, {'Set',a,b}), ok = and_same_var(42), {'EXIT',{if_clause,_}} = (catch and_same_var(x)), @@ -844,18 +844,18 @@ relprod(R1, R2) when (erlang:size(R1) =:= 3) and (erlang:element(1,R1) =:= 'Set' xor_guard(Config) when is_list(Config) -> %% 'xor' combinations of literal true/false. - ?line check(fun() -> if true xor false -> ok end end, ok), - ?line check(fun() -> if false xor true -> ok end end, ok), - ?line check(fun() -> if true xor true -> ok; true -> error end end, error), - ?line check(fun() -> if false xor false -> ok; true -> error end end, error), - ?line check(fun() -> - {'EXIT',{if_clause,_}} = (catch if false xor false -> ok end), - exit - end, exit), - ?line check(fun() -> - {'EXIT',{if_clause,_}} = (catch if true xor true -> ok end), - exit - end, exit), + check(fun() -> if true xor false -> ok end end, ok), + check(fun() -> if false xor true -> ok end end, ok), + check(fun() -> if true xor true -> ok; true -> error end end, error), + check(fun() -> if false xor false -> ok; true -> error end end, error), + check(fun() -> + {'EXIT',{if_clause,_}} = (catch if false xor false -> ok end), + exit + end, exit), + check(fun() -> + {'EXIT',{if_clause,_}} = (catch if true xor true -> ok end), + exit + end, exit), %% 'xor' combinations using variables containing true/false. @@ -863,18 +863,18 @@ xor_guard(Config) when is_list(Config) -> True = id(true), False = id(false), - ?line check(fun() -> if True xor False -> ok end end, ok), - ?line check(fun() -> if False xor True -> ok end end, ok), - ?line check(fun() -> if True xor True -> ok; true -> error end end, error), - ?line check(fun() -> if False xor False -> ok; true -> error end end, error), - ?line check(fun() -> - {'EXIT',{if_clause,_}} = (catch if False xor False -> ok end), - exit - end, exit), - ?line check(fun() -> - {'EXIT',{if_clause,_}} = (catch if True xor True -> ok end), - exit - end, exit), + check(fun() -> if True xor False -> ok end end, ok), + check(fun() -> if False xor True -> ok end end, ok), + check(fun() -> if True xor True -> ok; true -> error end end, error), + check(fun() -> if False xor False -> ok; true -> error end end, error), + check(fun() -> + {'EXIT',{if_clause,_}} = (catch if False xor False -> ok end), + exit + end, exit), + check(fun() -> + {'EXIT',{if_clause,_}} = (catch if True xor True -> ok end), + exit + end, exit), ok. @@ -883,53 +883,53 @@ more_xor_guards(Config) when is_list(Config) -> False = id(false), ATuple = id({false,true,gurka}), - ?line check(fun() -> - if element(42, ATuple) xor False -> ok; - true -> error end - end, error), - - ?line check(fun() -> - if False xor element(42, ATuple) xor False -> ok; - true -> error end - end, error), - - ?line check(fun() -> - if element(18, ATuple) xor element(42, ATuple) -> ok; - true -> error end - end, error), - - ?line check(fun() -> - if True xor element(42, ATuple) -> ok; - true -> error end - end, error), - - ?line check(fun() -> - if element(42, ATuple) xor True -> ok; - true -> error end - end, error), + check(fun() -> + if element(42, ATuple) xor False -> ok; + true -> error end + end, error), + + check(fun() -> + if False xor element(42, ATuple) xor False -> ok; + true -> error end + end, error), + + check(fun() -> + if element(18, ATuple) xor element(42, ATuple) -> ok; + true -> error end + end, error), + + check(fun() -> + if True xor element(42, ATuple) -> ok; + true -> error end + end, error), + + check(fun() -> + if element(42, ATuple) xor True -> ok; + true -> error end + end, error), ok. build_in_guard(Config) when is_list(Config) -> SubBin = <<5.0/float>>, - ?line B = <<1,SubBin/binary,3.5/float>>, - ?line if - B =:= <<1,SubBin/binary,3.5/float>> -> ok - end. + B = <<1,SubBin/binary,3.5/float>>, + if + B =:= <<1,SubBin/binary,3.5/float>> -> ok + end. old_guard_tests(Config) when list(Config) -> %% Check that all the old guard tests are still recognized. - ?line list = og(Config), - ?line atom = og(an_atom), - ?line binary = og(<<1,2>>), - ?line float = og(3.14), - ?line integer = og(43), - ?line a_function = og(fun() -> ok end), - ?line pid = og(self()), - ?line reference = og(make_ref()), - ?line tuple = og({}), - - ?line number = on(45.333), - ?line number = on(-19), + list = og(Config), + atom = og(an_atom), + binary = og(<<1,2>>), + float = og(3.14), + integer = og(43), + a_function = og(fun() -> ok end), + pid = og(self()), + reference = og(make_ref()), + tuple = og({}), + + number = on(45.333), + number = on(-19), ok. og(V) when atom(V) -> atom; @@ -948,8 +948,8 @@ on(V) when number(V) -> number; on(_) -> not_number. gbif(Config) when is_list(Config) -> - ?line error = gbif_1(1, {false,true}), - ?line ok = gbif_1(2, {false,true}), + error = gbif_1(1, {false,true}), + ok = gbif_1(2, {false,true}), ok. gbif_1(P, T) when element(P, T) -> ok; @@ -957,57 +957,57 @@ gbif_1(_, _) -> error. t_is_boolean(Config) when is_list(Config) -> - ?line true = is_boolean(true), - ?line true = is_boolean(false), - ?line true = is_boolean(id(true)), - ?line true = is_boolean(id(false)), - - ?line false = is_boolean(glurf), - ?line false = is_boolean(id(glurf)), - - ?line false = is_boolean([]), - ?line false = is_boolean(id([])), - ?line false = is_boolean(42), - ?line false = is_boolean(id(-42)), - - ?line false = is_boolean(math:pi()), - ?line false = is_boolean(384793478934378924978439789873478934897), - - ?line false = is_boolean(id(self())), - ?line false = is_boolean(id({x,y,z})), - ?line false = is_boolean(id([a,b,c])), - ?line false = is_boolean(id(make_ref())), - ?line false = is_boolean(id(<<1,2,3>>)), - ?line false = is_boolean({id(x),y,z}), - ?line false = is_boolean([id(a),b,c]), - - ?line ok = bool(true), - ?line ok = bool(false), - ?line ok = bool(id(true)), - ?line ok = bool(id(false)), - - ?line error = bool(glurf), - ?line error = bool(id(glurf)), - - ?line error = bool([]), - ?line error = bool(id([])), - ?line error = bool(42), - ?line error = bool(id(-42)), - - ?line error = bool(math:pi()), - ?line error = bool(384793478934378924978439789873478934897), - - ?line error = bool(id(self())), - ?line error = bool(id({x,y,z})), - ?line error = bool(id([a,b,c])), - ?line error = bool(id(make_ref())), - ?line error = bool(id(<<1,2,3>>)), - - ?line true = my_is_bool(true), - ?line true = my_is_bool(false), - ?line false = my_is_bool([]), - ?line false = my_is_bool([1,2,3,4]), - ?line false = my_is_bool({a,b,c}), + true = is_boolean(true), + true = is_boolean(false), + true = is_boolean(id(true)), + true = is_boolean(id(false)), + + false = is_boolean(glurf), + false = is_boolean(id(glurf)), + + false = is_boolean([]), + false = is_boolean(id([])), + false = is_boolean(42), + false = is_boolean(id(-42)), + + false = is_boolean(math:pi()), + false = is_boolean(384793478934378924978439789873478934897), + + false = is_boolean(id(self())), + false = is_boolean(id({x,y,z})), + false = is_boolean(id([a,b,c])), + false = is_boolean(id(make_ref())), + false = is_boolean(id(<<1,2,3>>)), + false = is_boolean({id(x),y,z}), + false = is_boolean([id(a),b,c]), + + ok = bool(true), + ok = bool(false), + ok = bool(id(true)), + ok = bool(id(false)), + + error = bool(glurf), + error = bool(id(glurf)), + + error = bool([]), + error = bool(id([])), + error = bool(42), + error = bool(id(-42)), + + error = bool(math:pi()), + error = bool(384793478934378924978439789873478934897), + + error = bool(id(self())), + error = bool(id({x,y,z})), + error = bool(id([a,b,c])), + error = bool(id(make_ref())), + error = bool(id(<<1,2,3>>)), + + true = my_is_bool(true), + true = my_is_bool(false), + false = my_is_bool([]), + false = my_is_bool([1,2,3,4]), + false = my_is_bool({a,b,c}), ok. @@ -1048,18 +1048,18 @@ is_function_2(Config) when is_list(Config) -> end. tricky(Config) when is_list(Config) -> - ?line not_ok = tricky_1(1, 2), - ?line not_ok = tricky_1(1, blurf), - ?line not_ok = tricky_1(foo, 2), - ?line not_ok = tricky_1(a, b), - - ?line error = tricky_2(0.5), - ?line error = tricky_2(a), - ?line error = tricky_2({a,b,c}), - - ?line false = rb(100000, [1], 42), - ?line true = rb(100000, [], 42), - ?line true = rb(555, [a,b,c], 19), + not_ok = tricky_1(1, 2), + not_ok = tricky_1(1, blurf), + not_ok = tricky_1(foo, 2), + not_ok = tricky_1(a, b), + + error = tricky_2(0.5), + error = tricky_2(a), + error = tricky_2({a,b,c}), + + false = rb(100000, [1], 42), + true = rb(100000, [], 42), + true = rb(555, [a,b,c], 19), ok. tricky_1(X, Y) when abs((X == 1) or (Y == 2)) -> ok; @@ -1097,40 +1097,40 @@ rb(_, _, _) -> false. rel_ops(Config) when is_list(Config) -> - ?line ?T(=/=, 1, 1.0), - ?line ?F(=/=, 2, 2), - ?line ?F(=/=, {a}, {a}), + ?T(=/=, 1, 1.0), + ?F(=/=, 2, 2), + ?F(=/=, {a}, {a}), - ?line ?F(/=, a, a), - ?line ?F(/=, 0, 0.0), - ?line ?T(/=, 0, 1), - ?line ?F(/=, {a}, {a}), + ?F(/=, a, a), + ?F(/=, 0, 0.0), + ?T(/=, 0, 1), + ?F(/=, {a}, {a}), - ?line ?T(==, 1, 1.0), - ?line ?F(==, a, {}), + ?T(==, 1, 1.0), + ?F(==, a, {}), - ?line ?F(=:=, 1, 1.0), - ?line ?T(=:=, 42.0, 42.0), + ?F(=:=, 1, 1.0), + ?T(=:=, 42.0, 42.0), - ?line ?F(>, a, b), - ?line ?T(>, 42, 1.0), - ?line ?F(>, 42, 42.0), + ?F(>, a, b), + ?T(>, 42, 1.0), + ?F(>, 42, 42.0), - ?line ?T(<, a, b), - ?line ?F(<, 42, 1.0), - ?line ?F(<, 42, 42.0), + ?T(<, a, b), + ?F(<, 42, 1.0), + ?F(<, 42, 42.0), - ?line ?T(=<, 1.5, 5), - ?line ?F(=<, -9, -100.344), - ?line ?T(=<, 42, 42.0), + ?T(=<, 1.5, 5), + ?F(=<, -9, -100.344), + ?T(=<, 42, 42.0), - ?line ?T(>=, 42, 42.0), - ?line ?F(>=, a, b), - ?line ?T(>=, 1.0, 0), + ?T(>=, 42, 42.0), + ?F(>=, a, b), + ?T(>=, 1.0, 0), %% Coverage of beam_block:is_exact_eq_ok/1 and collect/1. - ?line true = any_atom /= id(42), - ?line true = [] /= id(42), + true = any_atom /= id(42), + true = [] /= id(42), ok. @@ -1371,10 +1371,10 @@ literal_type_tests(Config) when is_list(Config) -> literal_type_tests_1(Config) -> %% Generate an Erlang module with all different type of type tests. - ?line Tests = make_test([{T,L} || T <- type_tests(), L <- literals()] ++ + Tests = make_test([{T,L} || T <- type_tests(), L <- literals()] ++ [{is_function,L1,L2} || L1 <- literals(), L2 <- literals()]), - ?line Mod = literal_test, + Mod = literal_test, Anno = erl_anno:new(0), Func = {function, Anno, test, 0, [{clause,Anno,[],[],Tests}]}, Form = [{attribute,Anno,module,Mod}, @@ -1382,24 +1382,24 @@ literal_type_tests_1(Config) -> Func, {eof,Anno}], %% Print generated code for inspection. - ?line lists:foreach(fun (F) -> io:put_chars([erl_pp:form(F),"\n"]) end, Form), + lists:foreach(fun (F) -> io:put_chars([erl_pp:form(F),"\n"]) end, Form), %% Test compile:form/1. This implies full optimization (default). - ?line {ok,Mod,Code1} = compile:forms(Form), - ?line smoke_disasm(Config, Mod, Code1), - ?line {module,Mod} = code:load_binary(Mod, Mod, Code1), - ?line Mod:test(), - ?line true = code:delete(Mod), - ?line code:purge(Mod), + {ok,Mod,Code1} = compile:forms(Form), + smoke_disasm(Config, Mod, Code1), + {module,Mod} = code:load_binary(Mod, Mod, Code1), + Mod:test(), + true = code:delete(Mod), + code:purge(Mod), %% Test compile:form/2. Turn off all optimizations. - ?line {ok,Mod,Code2} = compile:forms(Form, [binary,report,time, + {ok,Mod,Code2} = compile:forms(Form, [binary,report,time, no_copt,no_postopt]), - ?line smoke_disasm(Config, Mod, Code2), - ?line {module,Mod} = code:load_binary(Mod, Mod, Code2), - ?line Mod:test(), - ?line true = code:delete(Mod), - ?line code:purge(Mod), + smoke_disasm(Config, Mod, Code2), + {module,Mod} = code:load_binary(Mod, Mod, Code2), + Mod:test(), + true = code:delete(Mod), + code:purge(Mod), ok. make_test([{T,L1,L2}|Ts]) -> @@ -1427,7 +1427,7 @@ test(T, L1, L2) -> {match,Anno,{atom,Anno,Val},hd(E)}. smoke_disasm(Config, Mod, Bin) -> - Priv = ?config(priv_dir, Config), + Priv = proplists:get_value(priv_dir, Config), File = filename:join(Priv, atom_to_list(Mod)++".beam"), ok = file:write_file(File, Bin), test_lib:smoke_disasm(File). @@ -1459,30 +1459,30 @@ type_tests() -> is_function]. basic_andalso_orelse(Config) when is_list(Config) -> - ?line T = id({type,integers,23,42}), - ?line 65 = if - ((element(1, T) =:= type) andalso (tuple_size(T) =:= 4) andalso - element(2, T)) == integers -> - element(3, T) + element(4, T); - true -> error - end, - ?line 65 = case [] of - [] when ((element(1, T) =:= type) andalso (tuple_size(T) =:= 4) andalso - element(2, T)) == integers -> - element(3, T) + element(4, T) - end, - - ?line 42 = basic_rt({type,integers,40,2}), - ?line 5.0 = basic_rt({vector,{3.0,4.0}}), - ?line 20 = basic_rt(['+',3,7]), - ?line {'Set',a,b} = basic_rt({{'Set',a,b},{'Set',a,b}}), - ?line 12 = basic_rt({klurf,4}), - - ?line error = basic_rt({type,integers,40,2,3}), - ?line error = basic_rt({kalle,integers,40,2}), - ?line error = basic_rt({kalle,integers,40,2}), - ?line error = basic_rt({1,2}), - ?line error = basic_rt([]), + T = id({type,integers,23,42}), + 65 = if + ((element(1, T) =:= type) andalso (tuple_size(T) =:= 4) andalso + element(2, T)) == integers -> + element(3, T) + element(4, T); + true -> error + end, + 65 = case [] of + [] when ((element(1, T) =:= type) andalso (tuple_size(T) =:= 4) andalso + element(2, T)) == integers -> + element(3, T) + element(4, T) + end, + + 42 = basic_rt({type,integers,40,2}), + 5.0 = basic_rt({vector,{3.0,4.0}}), + 20 = basic_rt(['+',3,7]), + {'Set',a,b} = basic_rt({{'Set',a,b},{'Set',a,b}}), + 12 = basic_rt({klurf,4}), + + error = basic_rt({type,integers,40,2,3}), + error = basic_rt({kalle,integers,40,2}), + error = basic_rt({kalle,integers,40,2}), + error = basic_rt({1,2}), + error = basic_rt([]), RelProdBody = fun(R1, R2) -> @@ -1493,7 +1493,7 @@ basic_andalso_orelse(Config) when is_list(Config) -> end end, - ?line ok = RelProdBody({'Set',a,b}, {'Set',a,b}), + ok = RelProdBody({'Set',a,b}, {'Set',a,b}), %% 'andalso'/'orelse' with calls known to fail already at compile time. %% Used to crash the code generator. @@ -1564,14 +1564,14 @@ traverse_dcd({Cont,Recs},Log,Fun) -> check_qlc_hrl(Config) when is_list(Config) -> St = {r1,false,dum}, - ?line foo = cqlc(qlc, q, [{lc,1,2,3}], St), - ?line foo = cqlc(qlc, q, [{lc,1,2,3},b], St), - ?line St = cqlc(qlc, q, [], St), - ?line St = cqlc(qlc, blurf, [{lc,1,2,3},b], St), - ?line St = cqlc(q, q, [{lc,1,2,3},b], St), - ?line St = cqlc(qlc, q, [{lc,1,2,3},b,c], St), - ?line St = cqlc(qlc, q, [a,b], St), - ?line {r1,true,kalle} = cqlc(qlc, q, [{lc,1,2,3},b], {r1,true,kalle}), + foo = cqlc(qlc, q, [{lc,1,2,3}], St), + foo = cqlc(qlc, q, [{lc,1,2,3},b], St), + St = cqlc(qlc, q, [], St), + St = cqlc(qlc, blurf, [{lc,1,2,3},b], St), + St = cqlc(q, q, [{lc,1,2,3},b], St), + St = cqlc(qlc, q, [{lc,1,2,3},b,c], St), + St = cqlc(qlc, q, [a,b], St), + {r1,true,kalle} = cqlc(qlc, q, [{lc,1,2,3},b], {r1,true,kalle}), ok. %% From erl_lint.erl; original name was check_qlc_hrl/4. @@ -1588,13 +1588,13 @@ cqlc(M, F, As, St) -> %% OTP-7679: Thanks to Hunter Morris. andalso_semi(Config) when is_list(Config) -> - ?line ok = andalso_semi_foo(0), - ?line ok = andalso_semi_foo(1), - ?line fc(catch andalso_semi_foo(2)), + ok = andalso_semi_foo(0), + ok = andalso_semi_foo(1), + fc(catch andalso_semi_foo(2)), - ?line ok = andalso_semi_bar([a,b,c]), - ?line ok = andalso_semi_bar(1), - ?line fc(catch andalso_semi_bar([a,b])), + ok = andalso_semi_bar([a,b,c]), + ok = andalso_semi_bar(1), + fc(catch andalso_semi_bar([a,b])), ok. andalso_semi_foo(Bar) when is_integer(Bar) andalso Bar =:= 0; Bar =:= 1 -> @@ -1605,20 +1605,20 @@ andalso_semi_bar(Bar) when is_list(Bar) andalso length(Bar) =:= 3; Bar =:= 1 -> t_tuple_size(Config) when is_list(Config) -> - ?line 10 = do_tuple_size({1,2,3,4}), - ?line fc(catch do_tuple_size({1,2,3})), - ?line fc(catch do_tuple_size(42)), + 10 = do_tuple_size({1,2,3,4}), + fc(catch do_tuple_size({1,2,3})), + fc(catch do_tuple_size(42)), - ?line error = ludicrous_tuple_size({a,b,c}), - ?line error = ludicrous_tuple_size([a,b,c]), + error = ludicrous_tuple_size({a,b,c}), + error = ludicrous_tuple_size([a,b,c]), %% Test the "unsafe case" - the register assigned the tuple size is %% not killed. - ?line DataDir = test_lib:get_data_dir(Config), - ?line File = filename:join(DataDir, "guard_SUITE_tuple_size"), - ?line {ok,Mod,Code} = compile:file(File, [from_asm,binary]), - ?line code:load_binary(Mod, File, Code), - ?line 14 = Mod:t({1,2,3,4}), + DataDir = test_lib:get_data_dir(Config), + File = filename:join(DataDir, "guard_SUITE_tuple_size"), + {ok,Mod,Code} = compile:file(File, [from_asm,binary]), + code:load_binary(Mod, File, Code), + 14 = Mod:t({1,2,3,4}), _ = code:delete(Mod), _ = code:purge(Mod), @@ -1647,71 +1647,70 @@ mask_error({'EXIT',{Err,_}}) -> mask_error(Else) -> Else. -binary_part(doc) -> - ["Tests the binary_part/2,3 guard (GC) bif's"]; +%% Test the binary_part/2,3 guard (GC) BIFs. binary_part(Config) when is_list(Config) -> %% This is more or less a copy of what the guard_SUITE in emulator %% does to cover the guard bif's - ?line 1 = bptest(<<1,2,3>>), - ?line 2 = bptest(<<2,1,3>>), - ?line error = bptest(<<1>>), - ?line error = bptest(<<>>), - ?line error = bptest(apa), - ?line 3 = bptest(<<2,3,3>>), + 1 = bptest(<<1,2,3>>), + 2 = bptest(<<2,1,3>>), + error = bptest(<<1>>), + error = bptest(<<>>), + error = bptest(apa), + 3 = bptest(<<2,3,3>>), % With one variable (pos) - ?line 1 = bptest(<<1,2,3>>,1), - ?line 2 = bptest(<<2,1,3>>,1), - ?line error = bptest(<<1>>,1), - ?line error = bptest(<<>>,1), - ?line error = bptest(apa,1), - ?line 3 = bptest(<<2,3,3>>,1), + 1 = bptest(<<1,2,3>>,1), + 2 = bptest(<<2,1,3>>,1), + error = bptest(<<1>>,1), + error = bptest(<<>>,1), + error = bptest(apa,1), + 3 = bptest(<<2,3,3>>,1), % With one variable (length) - ?line 1 = bptesty(<<1,2,3>>,1), - ?line 2 = bptesty(<<2,1,3>>,1), - ?line error = bptesty(<<1>>,1), - ?line error = bptesty(<<>>,1), - ?line error = bptesty(apa,1), - ?line 3 = bptesty(<<2,3,3>>,2), + 1 = bptesty(<<1,2,3>>,1), + 2 = bptesty(<<2,1,3>>,1), + error = bptesty(<<1>>,1), + error = bptesty(<<>>,1), + error = bptesty(apa,1), + 3 = bptesty(<<2,3,3>>,2), % With one variable (whole tuple) - ?line 1 = bptestx(<<1,2,3>>,{1,1}), - ?line 2 = bptestx(<<2,1,3>>,{1,1}), - ?line error = bptestx(<<1>>,{1,1}), - ?line error = bptestx(<<>>,{1,1}), - ?line error = bptestx(apa,{1,1}), - ?line 3 = bptestx(<<2,3,3>>,{1,2}), + 1 = bptestx(<<1,2,3>>,{1,1}), + 2 = bptestx(<<2,1,3>>,{1,1}), + error = bptestx(<<1>>,{1,1}), + error = bptestx(<<>>,{1,1}), + error = bptestx(apa,{1,1}), + 3 = bptestx(<<2,3,3>>,{1,2}), % With two variables - ?line 1 = bptest(<<1,2,3>>,1,1), - ?line 2 = bptest(<<2,1,3>>,1,1), - ?line error = bptest(<<1>>,1,1), - ?line error = bptest(<<>>,1,1), - ?line error = bptest(apa,1,1), - ?line 3 = bptest(<<2,3,3>>,1,2), + 1 = bptest(<<1,2,3>>,1,1), + 2 = bptest(<<2,1,3>>,1,1), + error = bptest(<<1>>,1,1), + error = bptest(<<>>,1,1), + error = bptest(apa,1,1), + 3 = bptest(<<2,3,3>>,1,2), % Direct (autoimported) call, these will be evaluated by the compiler... - ?line <<2>> = binary_part(<<1,2,3>>,1,1), - ?line <<1>> = binary_part(<<2,1,3>>,1,1), + <<2>> = binary_part(<<1,2,3>>,1,1), + <<1>> = binary_part(<<2,1,3>>,1,1), % Compiler warnings due to constant evaluation expected (3) - ?line badarg = ?MASK_ERROR(binary_part(<<1>>,1,1)), - ?line badarg = ?MASK_ERROR(binary_part(<<>>,1,1)), - ?line badarg = ?MASK_ERROR(binary_part(apa,1,1)), - ?line <<3,3>> = binary_part(<<2,3,3>>,1,2), + badarg = ?MASK_ERROR(binary_part(<<1>>,1,1)), + badarg = ?MASK_ERROR(binary_part(<<>>,1,1)), + badarg = ?MASK_ERROR(binary_part(apa,1,1)), + <<3,3>> = binary_part(<<2,3,3>>,1,2), % Direct call through apply - ?line <<2>> = apply(erlang,binary_part,[<<1,2,3>>,1,1]), - ?line <<1>> = apply(erlang,binary_part,[<<2,1,3>>,1,1]), + <<2>> = apply(erlang,binary_part,[<<1,2,3>>,1,1]), + <<1>> = apply(erlang,binary_part,[<<2,1,3>>,1,1]), % Compiler warnings due to constant evaluation expected (3) - ?line badarg = ?MASK_ERROR(apply(erlang,binary_part,[<<1>>,1,1])), - ?line badarg = ?MASK_ERROR(apply(erlang,binary_part,[<<>>,1,1])), - ?line badarg = ?MASK_ERROR(apply(erlang,binary_part,[apa,1,1])), - ?line <<3,3>> = apply(erlang,binary_part,[<<2,3,3>>,1,2]), + badarg = ?MASK_ERROR(apply(erlang,binary_part,[<<1>>,1,1])), + badarg = ?MASK_ERROR(apply(erlang,binary_part,[<<>>,1,1])), + badarg = ?MASK_ERROR(apply(erlang,binary_part,[apa,1,1])), + <<3,3>> = apply(erlang,binary_part,[<<2,3,3>>,1,2]), % Constant propagation - ?line Bin = <<1,2,3>>, - ?line ok = if + Bin = <<1,2,3>>, + ok = if binary_part(Bin,1,1) =:= <<2>> -> ok; %% Compiler warning, clause cannot match (expected) true -> error end, - ?line ok = if + ok = if binary_part(Bin,{1,1}) =:= <<2>> -> ok; %% Compiler warning, clause cannot match (expected) @@ -1778,24 +1777,24 @@ bptest(_,_,_) -> -define(FAILING(C), if - C -> ?t:fail(should_fail); + C -> ct:fail(should_fail); true -> ok end, if - true, C -> ?t:fail(should_fail); + true, C -> ct:fail(should_fail); true -> ok end). bad_constants(Config) when is_list(Config) -> - ?line ?FAILING(false), - ?line ?FAILING([]), - ?line ?FAILING([a]), - ?line ?FAILING([Config]), - ?line ?FAILING({a,b}), - ?line ?FAILING({a,Config}), - ?line ?FAILING(<<1>>), - ?line ?FAILING(42), - ?line ?FAILING(3.14), + ?FAILING(false), + ?FAILING([]), + ?FAILING([a]), + ?FAILING([Config]), + ?FAILING({a,b}), + ?FAILING({a,Config}), + ?FAILING(<<1>>), + ?FAILING(42), + ?FAILING(3.14), ok. bad_guards(Config) when is_list(Config) -> @@ -1915,7 +1914,7 @@ check(F, Result) -> Other -> io:format("Expected: ~p\n", [Result]), io:format(" Got: ~p\n", [Other]), - test_server:fail() + ct:fail(check_failed) end. fc({'EXIT',{function_clause,_}}) -> ok; diff --git a/lib/compiler/test/inline_SUITE.erl b/lib/compiler/test/inline_SUITE.erl index 0b92a784de..4c53b96fe6 100644 --- a/lib/compiler/test/inline_SUITE.erl +++ b/lib/compiler/test/inline_SUITE.erl @@ -21,7 +21,7 @@ -module(inline_SUITE). --include_lib("test_server/include/test_server.hrl"). +-include_lib("common_test/include/ct.hrl"). -compile(export_all). -compile({inline,[badarg/2]}). @@ -47,8 +47,8 @@ init_per_suite(Config) -> [{testing_node,Node}|Config]. end_per_suite(Config) -> - Node = ?config(testing_node, Config), - ?t:stop_node(Node), + Node = proplists:get_value(testing_node, Config), + test_server:stop_node(Node), ok. init_per_group(_GroupName, Config) -> @@ -60,16 +60,16 @@ end_per_group(_GroupName, Config) -> attribute(Config) when is_list(Config) -> Name = "attribute", - ?line Src = filename:join(?config(data_dir, Config), Name), - ?line Out = ?config(priv_dir,Config), + Src = filename:join(proplists:get_value(data_dir, Config), Name), + Out = proplists:get_value(priv_dir,Config), - ?line {ok,attribute=Mod} = compile:file(Src, [{outdir,Out},report,time]), - ?line Outfile = filename:join(Out, Name++".beam"), - ?line {ok,{Mod,[{locals,Locals}]}} = beam_lib:chunks(Outfile, [locals]), - ?line io:format("locals: ~p\n", [Locals]), + {ok,attribute=Mod} = compile:file(Src, [{outdir,Out},report,time]), + Outfile = filename:join(Out, Name++".beam"), + {ok,{Mod,[{locals,Locals}]}} = beam_lib:chunks(Outfile, [locals]), + io:format("locals: ~p\n", [Locals]), %% The inliner should have removed all local functions. - ?line [] = Locals, + [] = Locals, ok. @@ -89,48 +89,46 @@ attribute(Config) when is_list(Config) -> ?comp(maps_inline_test). try_inline(Mod, Config) -> - Node = ?config(testing_node, Config), - ?line Src = filename:join(?config(data_dir, Config), atom_to_list(Mod)), - ?line Out = ?config(priv_dir,Config), + Node = proplists:get_value(testing_node, Config), + Src = filename:join(proplists:get_value(data_dir, Config), + atom_to_list(Mod)), + Out = proplists:get_value(priv_dir,Config), %% Normal compilation. - ?line io:format("Compiling: ~s\n", [Src]), - ?line {ok,Mod} = compile:file(Src, [{outdir,Out},report,bin_opt_info,clint]), + io:format("Compiling: ~s\n", [Src]), + {ok,Mod} = compile:file(Src, [{outdir,Out},report,bin_opt_info,clint]), - ?line Dog = test_server:timetrap(test_server:minutes(10)), - ?line NormalResult = rpc:call(Node, ?MODULE, load_and_call, [Out,Mod]), - ?line test_server:timetrap_cancel(Dog), + ct:timetrap({minutes,10}), + NormalResult = rpc:call(Node, ?MODULE, load_and_call, [Out,Mod]), %% Inlining. - ?line io:format("Compiling with old inliner: ~s\n", [Src]), - ?line {ok,Mod} = compile:file(Src, [{outdir,Out},report,bin_opt_info, + io:format("Compiling with old inliner: ~s\n", [Src]), + {ok,Mod} = compile:file(Src, [{outdir,Out},report,bin_opt_info, {inline,1000},clint]), %% Run inlined code. - ?line Dog3 = test_server:timetrap(test_server:minutes(10)), - ?line OldInlinedResult = rpc:call(Node, ?MODULE, load_and_call, [Out,Mod]), - ?line test_server:timetrap_cancel(Dog3), + ct:timetrap({minutes,10}), + OldInlinedResult = rpc:call(Node, ?MODULE, load_and_call, [Out,Mod]), %% Compare results. - ?line compare(NormalResult, OldInlinedResult), - ?line NormalResult = OldInlinedResult, + compare(NormalResult, OldInlinedResult), + NormalResult = OldInlinedResult, %% Inlining. - ?line io:format("Compiling with new inliner: ~s\n", [Src]), - ?line {ok,Mod} = compile:file(Src, [{outdir,Out},report, + io:format("Compiling with new inliner: ~s\n", [Src]), + {ok,Mod} = compile:file(Src, [{outdir,Out},report, bin_opt_info,inline,clint]), %% Run inlined code. - ?line Dog4 = test_server:timetrap(test_server:minutes(10)), - ?line InlinedResult = rpc:call(Node, ?MODULE, load_and_call, [Out,Mod]), - ?line test_server:timetrap_cancel(Dog4), + ct:timetrap({minutes,10}), + InlinedResult = rpc:call(Node, ?MODULE, load_and_call, [Out,Mod]), %% Compare results. - ?line compare(NormalResult, InlinedResult), - ?line NormalResult = InlinedResult, + compare(NormalResult, InlinedResult), + NormalResult = InlinedResult, %% Delete Beam file. - ?line ok = file:delete(filename:join(Out, atom_to_list(Mod)++code:objfile_extension())), + ok = file:delete(filename:join(Out, atom_to_list(Mod)++code:objfile_extension())), ok. @@ -142,24 +140,24 @@ compare([{X,Y,RGB1}|T1], [{X,Y,RGB2}|T2]) -> compare(T1, T2); compare([H1|_], [H2|_]) -> io:format("Normal = ~p, Inlined = ~p\n", [H1,H2]), - ?t:fail(); + ct:fail(different); compare([], []) -> ok. start_node(Name, Args) -> case test_server:start_node(Name, slave, [{args,Args}]) of {ok,Node} -> {ok, Node}; - Error -> ?line test_server:fail(Error) + Error -> ct:fail(Error) end. load_and_call(Out, Module) -> - ?line io:format("Loading...\n",[]), - ?line code:purge(Module), - ?line LoadRc = code:load_abs(filename:join(Out, Module)), - ?line {module,Module} = LoadRc, - - ?line io:format("Calling...\n",[]), - ?line {Time,CallResult} = timer:tc(Module, Module, []), - ?line io:format("Time: ~p\n", [Time]), + io:format("Loading...\n",[]), + code:purge(Module), + LoadRc = code:load_abs(filename:join(Out, Module)), + {module,Module} = LoadRc, + + io:format("Calling...\n",[]), + {Time,CallResult} = timer:tc(Module, Module, []), + io:format("Time: ~p\n", [Time]), CallResult. %% Macros used by lists/1 below. @@ -195,69 +193,78 @@ load_and_call(Out, Module) -> %% Note: This module must be compiled with the inline_lists_funcs option. lists(Config) when is_list(Config) -> - ?line List = lists:seq(1, 20), + List = lists:seq(1, 20), %% lists:map/2 - ?line ?TestHighOrder_2(map, (fun(E) -> - R = E band 16#ff, - put(?MODULE, [E|get(?MODULE)]), - R - end), List), + ?TestHighOrder_2(map, + (fun(E) -> + R = E band 16#ff, + put(?MODULE, [E|get(?MODULE)]), + R + end), List), %% lists:flatmap/2 - ?line ?TestHighOrder_2(flatmap, (fun(E) -> - R = lists:duplicate(E, E), - put(?MODULE, [E|get(?MODULE)]), - R - end), List), + ?TestHighOrder_2(flatmap, + (fun(E) -> + R = lists:duplicate(E, E), + put(?MODULE, [E|get(?MODULE)]), + R + end), List), %% lists:foreach/2 - ?line ?TestHighOrder_2(foreach, - (fun(E) -> - put(?MODULE, [E bor 7|get(?MODULE)]) - end), List), + ?TestHighOrder_2(foreach, + (fun(E) -> + put(?MODULE, [E bor 7|get(?MODULE)]) + end), List), %% lists:filter/2 - ?line ?TestHighOrder_2(filter, (fun(E) -> - put(?MODULE, [E|get(?MODULE)]), - (E bsr 1) band 1 =/= 0 - end), List), + ?TestHighOrder_2(filter, + (fun(E) -> + put(?MODULE, [E|get(?MODULE)]), + (E bsr 1) band 1 =/= 0 + end), List), %% lists:any/2 - ?line ?TestHighOrder_2(any, (fun(E) -> - put(?MODULE, [E|get(?MODULE)]), - false %Force it to go through all. - end), List), + ?TestHighOrder_2(any, + (fun(E) -> + put(?MODULE, [E|get(?MODULE)]), + false %Force it to go through all. + end), List), %% lists:all/2 - ?line ?TestHighOrder_2(all, (fun(E) -> - put(?MODULE, [E|get(?MODULE)]), - true %Force it to go through all. - end), List), + ?TestHighOrder_2(all, + (fun(E) -> + put(?MODULE, [E|get(?MODULE)]), + true %Force it to go through all. + end), List), %% lists:foldl/3 - ?line ?TestHighOrder_3(foldl, (fun(E, A) -> - put(?MODULE, [E|get(?MODULE)]), - A bxor E - end), 0, List), + ?TestHighOrder_3(foldl, + (fun(E, A) -> + put(?MODULE, [E|get(?MODULE)]), + A bxor E + end), 0, List), %% lists:foldr/3 - ?line ?TestHighOrder_3(foldr, (fun(E, A) -> - put(?MODULE, [E|get(?MODULE)]), - A bxor (bnot E) - end), 0, List), + ?TestHighOrder_3(foldr, + (fun(E, A) -> + put(?MODULE, [E|get(?MODULE)]), + A bxor (bnot E) + end), 0, List), %% lists:mapfoldl/3 - ?line ?TestHighOrder_3(mapfoldl, (fun(E, A) -> - put(?MODULE, [E|get(?MODULE)]), - {bnot E,A bxor (bnot E)} - end), 0, List), + ?TestHighOrder_3(mapfoldl, + (fun(E, A) -> + put(?MODULE, [E|get(?MODULE)]), + {bnot E,A bxor (bnot E)} + end), 0, List), %% lists:mapfoldr/3 - ?line ?TestHighOrder_3(mapfoldr, (fun(E, A) -> - put(?MODULE, [E|get(?MODULE)]), - {bnot E,A bxor (bnot E)} - end), 0, List), + ?TestHighOrder_3(mapfoldr, + (fun(E, A) -> + put(?MODULE, [E|get(?MODULE)]), + {bnot E,A bxor (bnot E)} + end), 0, List), %% Cleanup. erase(?MODULE), @@ -330,7 +337,7 @@ badarg(Reply, _A) -> Reply. otp_7223(Config) when is_list(Config) -> - ?line {'EXIT', {{case_clause,{1}},_}} = (catch otp_7223_1(1)), + {'EXIT', {{case_clause,{1}},_}} = (catch otp_7223_1(1)), ok. -compile({inline,[{otp_7223_1,1}]}). @@ -343,7 +350,7 @@ otp_7223_2({a}) -> coverage(Config) when is_list(Config) -> Mod = bsdecode, - Src = filename:join(?config(data_dir, Config), Mod), + Src = filename:join(proplists:get_value(data_dir, Config), Mod), {ok,Mod,_} = compile:file(Src, [binary,report,{inline,0},clint]), {ok,Mod,_} = compile:file(Src, [binary,report,{inline,20}, verbose,clint]), diff --git a/lib/compiler/test/lc_SUITE.erl b/lib/compiler/test/lc_SUITE.erl index d10839ccf2..70c80d3353 100644 --- a/lib/compiler/test/lc_SUITE.erl +++ b/lib/compiler/test/lc_SUITE.erl @@ -26,9 +26,11 @@ empty_generator/1,no_export/1,shadow/1, effect/1]). --include_lib("test_server/include/test_server.hrl"). +-include_lib("common_test/include/ct.hrl"). -suite() -> [{ct_hooks,[ts_install_cth]}]. +suite() -> + [{ct_hooks,[ts_install_cth]}, + {timetrap,{minutes,1}}]. all() -> test_lib:recompile(?MODULE), @@ -59,12 +61,9 @@ end_per_group(_GroupName, Config) -> init_per_testcase(Case, Config) when is_atom(Case), is_list(Config) -> - Dog = test_server:timetrap(?t:minutes(1)), - [{watchdog,Dog}|Config]. + Config. end_per_testcase(Case, Config) when is_atom(Case), is_list(Config) -> - Dog = ?config(watchdog, Config), - ?t:timetrap_cancel(Dog), ok. basic(Config) when is_list(Config) -> @@ -171,7 +170,7 @@ no_gen_verify(Res, A, B) -> ShouldBe -> ok; _ -> io:format("A = ~p; B = ~p; Expected = ~p, actual = ~p", [A,B,ShouldBe,Res]), - ?t:fail() + ct:fail(failed) end. no_gen_eval(Fun, Res) -> diff --git a/lib/compiler/test/map_SUITE.erl b/lib/compiler/test/map_SUITE.erl index cff3b5deb4..14d175b92c 100644 --- a/lib/compiler/test/map_SUITE.erl +++ b/lib/compiler/test/map_SUITE.erl @@ -1479,7 +1479,7 @@ t_guard_fun(Config) when is_list(Config) -> {'EXIT', {function_clause,[{?MODULE,_,[#{s:=none,v:=none}],_}|_]}} -> ok; {'EXIT', {{case_clause,_},_}} -> {comment,inlined}; Other -> - test_server:fail({no_match, Other}) + ct:fail({no_match, Other}) end. @@ -1565,7 +1565,7 @@ t_build_and_match_empty_val(Config) when is_list(Config) -> {'EXIT',{function_clause,_}} -> ok; {'EXIT', {{case_clause,_},_}} -> {comment,inlined}; Other -> - test_server:fail({no_match, Other}) + ct:fail({no_match, Other}) end. t_build_and_match_val(Config) when is_list(Config) -> @@ -1583,7 +1583,7 @@ t_build_and_match_val(Config) when is_list(Config) -> {'EXIT',{function_clause,_}} -> ok; {'EXIT', {{case_clause,_},_}} -> {comment,inlined}; Other -> - test_server:fail({no_match, Other}) + ct:fail({no_match, Other}) end. t_build_and_match_nil(Config) when is_list(Config) -> @@ -1885,7 +1885,7 @@ register_corruption_dummy_call(A,B,C) -> {A,B,C}. t_frequency_table(Config) when is_list(Config) -> - random:seed({13,1337,54}), % pseudo random + rand:seed(exsplus, {13,1337,54}), % pseudo random N = 100000, Ts = rand_terms(N), #{ n:=N, tf := Tf } = frequency_table(Ts,#{ n=>0, tf => #{}}), @@ -1928,7 +1928,7 @@ rand_terms(0) -> []; rand_terms(N) -> [rand_term()|rand_terms(N-1)]. rand_term() -> - case random:uniform(6) of + case rand:uniform(6) of 1 -> rand_binary(); 2 -> rand_number(); 3 -> rand_atom(); @@ -1938,21 +1938,21 @@ rand_term() -> end. rand_binary() -> - case random:uniform(3) of + case rand:uniform(3) of 1 -> <<>>; 2 -> <<"hi">>; 3 -> <<"message text larger than 64 bytes. yep, message text larger than 64 bytes.">> end. rand_number() -> - case random:uniform(3) of - 1 -> random:uniform(5); - 2 -> float(random:uniform(5)); - 3 -> 1 bsl (63 + random:uniform(3)) + case rand:uniform(3) of + 1 -> rand:uniform(5); + 2 -> float(rand:uniform(5)); + 3 -> 1 bsl (63 + rand:uniform(3)) end. rand_atom() -> - case random:uniform(3) of + case rand:uniform(3) of 1 -> hi; 2 -> some_atom; 3 -> some_other_atom @@ -1960,21 +1960,21 @@ rand_atom() -> rand_tuple() -> - case random:uniform(3) of + case rand:uniform(3) of 1 -> {ok, rand_term()}; % careful 2 -> {1, 2, 3}; 3 -> {<<"yep">>, 1337} end. rand_list() -> - case random:uniform(3) of + case rand:uniform(3) of 1 -> "hi"; 2 -> [1,rand_term()]; % careful 3 -> [improper|list] end. rand_map() -> - case random:uniform(3) of + case rand:uniform(3) of 1 -> #{ hi => 3 }; 2 -> #{ wat => rand_term(), other => 3 }; % careful 3 -> #{ hi => 42, other => 42, yet_anoter => 1337 } diff --git a/lib/compiler/test/match_SUITE.erl b/lib/compiler/test/match_SUITE.erl index 67d668f650..41fa1603ef 100644 --- a/lib/compiler/test/match_SUITE.erl +++ b/lib/compiler/test/match_SUITE.erl @@ -26,7 +26,7 @@ selectify/1,underscore/1,match_map/1,map_vars_used/1, coverage/1]). --include_lib("test_server/include/test_server.hrl"). +-include_lib("common_test/include/ct.hrl"). suite() -> [{ct_hooks,[ts_install_cth]}]. @@ -55,10 +55,10 @@ end_per_group(_GroupName, Config) -> pmatch(Config) when is_list(Config) -> - ?line ok = doit(1), - ?line ok = doit(2), - ?line {error,baz} = doit(3), - ?line {error,foobar} = doit(4), + ok = doit(1), + ok = doit(2), + {error,baz} = doit(3), + {error,foobar} = doit(4), ok. %% Thanks to Tobias Lindahl (HiPE). @@ -78,13 +78,13 @@ doit(X) -> end. mixed(Config) when is_list(Config) -> - ?line glufs = mixit(1), - ?line klafs = mixit(2), - ?line fnurra = mixit(3), - ?line usch = mixit(4), - ?line {error,blurf} = mixit(5), - ?line {error,87987987} = mixit(6), - ?line {error,{a,b,c}} = mixit(7), + glufs = mixit(1), + klafs = mixit(2), + fnurra = mixit(3), + usch = mixit(4), + {error,blurf} = mixit(5), + {error,87987987} = mixit(6), + {error,{a,b,c}} = mixit(7), ok. mixit(X) -> @@ -106,41 +106,41 @@ mixit(X) -> aliases(Config) when is_list(Config) -> %% Lists/strings. - ?line ok = str_alias("abc"), - ?line ok = str_alias("def"), - ?line ok = str_alias("ghi"), - ?line ok = str_alias("klm"), - ?line ok = str_alias("qrs"), - ?line ok = str_alias("xy"), - ?line ok = str_alias(""), - ?line ok = str_alias([]), - ?line error = str_alias("blurf"), + ok = str_alias("abc"), + ok = str_alias("def"), + ok = str_alias("ghi"), + ok = str_alias("klm"), + ok = str_alias("qrs"), + ok = str_alias("xy"), + ok = str_alias(""), + ok = str_alias([]), + error = str_alias("blurf"), %% Characters/integers. - ?line ok = char_alias($v), - ?line ok = char_alias(118), - ?line ok = char_alias($w), - ?line ok = char_alias(119), - ?line ok = char_alias(42), - ?line ok = char_alias(3.0), - ?line error = char_alias($_), - ?line error = char_alias(0), - - ?line {42,42,42} = three(42), - - ?line {1,42,99,1,42,99} = tuple_alias({1,42,99}), - ?line {-10,20,-10,20,-10,20} = tuple_alias({-10,20}), - ?line 6 = tup_lit_alias({1,2,3}), - ?line 6 = tup_lit_alias_rev({1,2,3}), - - ?line {42,42,42,42} = multiple_aliases_1(42), - ?line {7,7,7} = multiple_aliases_2(7), - ?line {{a,b},{a,b},{a,b}} = multiple_aliases_3({a,b}), + ok = char_alias($v), + ok = char_alias(118), + ok = char_alias($w), + ok = char_alias(119), + ok = char_alias(42), + ok = char_alias(3.0), + error = char_alias($_), + error = char_alias(0), + + {42,42,42} = three(42), + + {1,42,99,1,42,99} = tuple_alias({1,42,99}), + {-10,20,-10,20,-10,20} = tuple_alias({-10,20}), + 6 = tup_lit_alias({1,2,3}), + 6 = tup_lit_alias_rev({1,2,3}), + + {42,42,42,42} = multiple_aliases_1(42), + {7,7,7} = multiple_aliases_2(7), + {{a,b},{a,b},{a,b}} = multiple_aliases_3({a,b}), %% Lists/literals. - ?line {a,b} = list_alias1([a,b]), - ?line {a,b} = list_alias2([a,b]), - ?line {a,b} = list_alias3([a,b]), + {a,b} = list_alias1([a,b]), + {a,b} = list_alias2([a,b]), + {a,b} = list_alias3([a,b]), %% Non-matching aliases. none = mixed_aliases(<<42>>), @@ -261,14 +261,14 @@ mixed_aliases(_) -> none. %% OTP-7018. match_in_call(Config) when is_list(Config) -> - ?line mac_a(0), - ?line mac_b(1), - ?line mac_c(42), - ?line mac_d(42), - ?line mac_e({gurka,42}), + mac_a(0), + mac_b(1), + mac_c(42), + mac_d(42), + mac_e({gurka,42}), - ?line [{2,2},{2,2}] = mac_lc([{2,any},{2,2}]), - ?line {'EXIT',_} = (catch mac_lc([{1,1}])), + [{2,2},{2,2}] = mac_lc([{2,any},{2,2}]), + {'EXIT',_} = (catch mac_lc([{1,1}])), ok. @@ -313,8 +313,8 @@ gurka({gurka,X}, X) -> ok. untuplify(Config) when is_list(Config) -> %% We do this to cover sys_core_fold:unalias_pat/1. - ?line {1,2,3,4,alias,{[1,2],{3,4},alias}} = untuplify_1([1,2], {3,4}, alias), - ?line error = untuplify_1([1,2], {3,4}, 42), + {1,2,3,4,alias,{[1,2],{3,4},alias}} = untuplify_1([1,2], {3,4}, alias), + error = untuplify_1([1,2], {3,4}, 42), ok. untuplify_1(A, B, C) -> @@ -329,11 +329,11 @@ untuplify_1(A, B, C) -> %% Coverage of beam_dead:shortcut_boolean_label/4. shortcut_boolean(Config) when is_list(Config) -> - ?line false = shortcut_boolean_1([0]), - ?line true = shortcut_boolean_1({42}), - ?line maybe = shortcut_boolean_1(self()), - ?line {'EXIT',_} = (catch shortcut_boolean_1([a,b])), - ?line {'EXIT',_} = (catch shortcut_boolean_1({a,b})), + false = shortcut_boolean_1([0]), + true = shortcut_boolean_1({42}), + maybe = shortcut_boolean_1(self()), + {'EXIT',_} = (catch shortcut_boolean_1([a,b])), + {'EXIT',_} = (catch shortcut_boolean_1({a,b})), ok. shortcut_boolean_1(X) -> @@ -352,8 +352,8 @@ shortcut_boolean_1(X) -> %% Test sys_core_fold:letify_guard/3. letify_guard(Config) when is_list(Config) -> - ?line {-15,a} = letify_guard(-15, a), - ?line 5 = letify_guard(2, 3), + {-15,a} = letify_guard(-15, a), + 5 = letify_guard(2, 3), ok. letify_guard(A, B) -> @@ -369,18 +369,18 @@ letify_guard(A, B) -> %% instructions in beam_dead and beam_peep. selectify(Config) when is_list(Config) -> - ?line integer = sel_different_types({r,42}), - ?line atom = sel_different_types({r,forty_two}), - ?line none = sel_different_types({r,18}), - ?line {'EXIT',_} = (catch sel_different_types([a,b,c])), - - ?line integer = sel_same_value({r,42}), - ?line error = sel_same_value({r,100}), - ?line error = sel_same_value(a), - - ?line integer42 = sel_same_value2(42), - ?line integer43 = sel_same_value2(43), - ?line error = sel_same_value2(44), + integer = sel_different_types({r,42}), + atom = sel_different_types({r,forty_two}), + none = sel_different_types({r,18}), + {'EXIT',_} = (catch sel_different_types([a,b,c])), + + integer = sel_same_value({r,42}), + error = sel_same_value({r,100}), + error = sel_same_value(a), + + integer42 = sel_same_value2(42), + integer43 = sel_same_value2(43), + error = sel_same_value2(44), ok. sel_different_types({r,_}=T) when element(2, T) =:= forty_two -> @@ -449,7 +449,10 @@ do_map_vars_used(X, Y, Map) -> coverage(Config) when is_list(Config) -> %% Cover beam_dead. ok = coverage_1(x, a), - ok = coverage_1(x, b). + ok = coverage_1(x, b), + + %% Cover sys_pre_expand. + ok = coverage_3("abc"). coverage_1(B, Tag) -> case Tag of @@ -460,4 +463,6 @@ coverage_1(B, Tag) -> coverage_2(1, a, x) -> ok; coverage_2(2, b, x) -> ok. +coverage_3([$a]++[]++"bc") -> ok. + id(I) -> I. diff --git a/lib/compiler/test/misc_SUITE.erl b/lib/compiler/test/misc_SUITE.erl index 8606935504..8a639f741f 100644 --- a/lib/compiler/test/misc_SUITE.erl +++ b/lib/compiler/test/misc_SUITE.erl @@ -25,7 +25,7 @@ tobias/1,empty_string/1,md5/1,silly_coverage/1, confused_literals/1,integer_encoding/1,override_bif/1]). --include_lib("test_server/include/test_server.hrl"). +-include_lib("common_test/include/ct.hrl"). %% For the override_bif testcase. %% NB, no other testcases in this testsuite can use these without erlang:prefix! @@ -38,22 +38,25 @@ -compile({no_auto_import,[byte_size/1]}). -import(erlang,[byte_size/1]). - +%% Cover the code for callback handling. +-callback must_define_this_one() -> 'ok'. +-callback do_something_strange(atom()) -> 'ok'. +-optional_callbacks([do_something_strange/1]). +-optional_callbacks([ignore_me]). %Invalid; ignored. %% Include an opaque declaration to cover the stripping of %% opaque types from attributes in v3_kernel. -opaque misc_SUITE_test_cases() :: [atom()]. init_per_testcase(Case, Config) when is_atom(Case), is_list(Config) -> - Dog = test_server:timetrap(?t:minutes(10)), - [{watchdog,Dog}|Config]. + Config. end_per_testcase(Case, Config) when is_atom(Case), is_list(Config) -> - Dog = ?config(watchdog, Config), - ?t:timetrap_cancel(Dog), ok. -suite() -> [{ct_hooks,[ts_install_cth]}]. +suite() -> + [{ct_hooks,[ts_install_cth]}, + {timetrap,{minutes,10}}]. -spec all() -> misc_SUITE_test_cases(). all() -> @@ -88,32 +91,27 @@ abs(_N) -> binary_part(_,_,_) -> dummy_bp. -% Make sure that auto-imported BIF's are overridden correctly - -override_bif(suite) -> - []; -override_bif(doc) -> - ["Test dat local functions and imports override auto-imported BIFs."]; +%% Test that local functions and imports override auto-imported BIFs. override_bif(Config) when is_list(Config) -> - ?line dummy_abs = abs(1), - ?line dummy_bp = binary_part(<<"hello">>,1,1), - ?line dummy = binary_part(<<"hello">>,{1,1}), - ?line 1 = erlang:abs(1), - ?line <<"e">> = erlang:binary_part(<<"hello">>,1,1), - ?line <<"e">> = erlang:binary_part(<<"hello">>,{1,1}), + dummy_abs = abs(1), + dummy_bp = binary_part(<<"hello">>,1,1), + dummy = binary_part(<<"hello">>,{1,1}), + 1 = erlang:abs(1), + <<"e">> = erlang:binary_part(<<"hello">>,1,1), + <<"e">> = erlang:binary_part(<<"hello">>,{1,1}), F = fun(X) when byte_size(X) =:= 4 -> four; (X) -> byte_size(X) end, - ?line four = F(<<1,2,3,4>>), - ?line 5 = F(<<1,2,3,4,5>>), + four = F(<<1,2,3,4>>), + 5 = F(<<1,2,3,4,5>>), ok. %% A bug reported by Tobias Lindahl for a development version of R11B. tobias(Config) when is_list(Config) -> - ?line 1 = tobias_1([1,2,3]), + 1 = tobias_1([1,2,3]), ok. tobias_1([H|_T]) -> @@ -134,7 +132,7 @@ tobias_2(_, _) -> -record(r, {s = ""}). empty_string(Config) when is_list(Config) -> - ?line #r{s="x"} = empty_string_1(#r{}), + #r{s="x"} = empty_string_1(#r{}), ok. empty_string_1(T) -> @@ -149,15 +147,15 @@ md5(Config) when is_list(Config) -> end. md5() -> - ?line Dir = filename:dirname(code:which(?MODULE)), - ?line Beams = filelib:wildcard(filename:join(Dir, "*.beam")), - ?line io:format("Found ~w beam files", [length(Beams)]), - ?line lists:foreach(fun md5_1/1, Beams). + Dir = filename:dirname(code:which(?MODULE)), + Beams = filelib:wildcard(filename:join(Dir, "*.beam")), + io:format("Found ~w beam files", [length(Beams)]), + lists:foreach(fun md5_1/1, Beams). md5_1(Beam) -> - ?line {ok,{Mod,[Vsn]}} = beam_lib:version(Beam), - ?line {ok,Code} = file:read_file(Beam), - ?line {Mod,<<Vsn:128>>} = {Mod,code:module_md5(Code)}. + {ok,{Mod,[Vsn]}} = beam_lib:version(Beam), + {ok,Code} = file:read_file(Beam), + {Mod,<<Vsn:128>>} = {Mod,code:module_md5(Code)}. %% Cover some code that handles internal errors. @@ -166,9 +164,9 @@ silly_coverage(Config) when is_list(Config) -> BadCoreErlang = {c_module,[], name,[],[], [{{c_var,[],{foo,2}},seriously_bad_body}]}, - ?line expect_error(fun() -> sys_core_fold:module(BadCoreErlang, []) end), - ?line expect_error(fun() -> sys_core_dsetel:module(BadCoreErlang, []) end), - ?line expect_error(fun() -> v3_kernel:module(BadCoreErlang, []) end), + expect_error(fun() -> sys_core_fold:module(BadCoreErlang, []) end), + expect_error(fun() -> sys_core_dsetel:module(BadCoreErlang, []) end), + expect_error(fun() -> v3_kernel:module(BadCoreErlang, []) end), %% v3_life BadKernel = {k_mdef,[],?MODULE, @@ -178,11 +176,11 @@ silly_coverage(Config) when is_list(Config) -> {k,[],[],[]}, f,0,[], seriously_bad_body}]}, - ?line expect_error(fun() -> v3_life:module(BadKernel, []) end), + expect_error(fun() -> v3_life:module(BadKernel, []) end), %% v3_codegen CodegenInput = {?MODULE,[{foo,0}],[],[{function,foo,0,[a|b],a,b,[]}]}, - ?line expect_error(fun() -> v3_codegen:module(CodegenInput, []) end), + expect_error(fun() -> v3_codegen:module(CodegenInput, []) end), %% beam_a BeamAInput = {?MODULE,[{foo,0}],[], @@ -192,13 +190,25 @@ silly_coverage(Config) when is_list(Config) -> {label,2}|non_proper_list]}],99}, expect_error(fun() -> beam_a:module(BeamAInput, []) end), + %% beam_reorder + BlockInput = {?MODULE,[{foo,0}],[], + [{function,foo,0,2, + [{label,1}, + {func_info,{atom,?MODULE},{atom,foo},0}, + {label,2}|non_proper_list]}],99}, + expect_error(fun() -> beam_reorder:module(BlockInput, []) end), + %% beam_block BlockInput = {?MODULE,[{foo,0}],[], [{function,foo,0,2, [{label,1}, {func_info,{atom,?MODULE},{atom,foo},0}, {label,2}|non_proper_list]}],99}, - ?line expect_error(fun() -> beam_block:module(BlockInput, []) end), + expect_error(fun() -> beam_block:module(BlockInput, []) end), + + %% beam_bs + BsInput = BlockInput, + expect_error(fun() -> beam_bs:module(BsInput, []) end), %% beam_type TypeInput = {?MODULE,[{foo,0}],[], @@ -224,7 +234,7 @@ silly_coverage(Config) when is_list(Config) -> [{label,1}, {func_info,{atom,?MODULE},{atom,foo},0}, {label,2}|non_proper_list]}],99}, - ?line expect_error(fun() -> beam_bool:module(BoolInput, []) end), + expect_error(fun() -> beam_bool:module(BoolInput, []) end), %% beam_dead. This is tricky. Our function must look OK to %% beam_utils:clean_labels/1, but must crash beam_dead. @@ -243,7 +253,7 @@ silly_coverage(Config) when is_list(Config) -> {func_info,{atom,?MODULE},{atom,foo},0}, {label,2}, {jump,{f,42}}]}],99}, - ?line expect_error(fun() -> beam_clean:module(CleanInput, []) end), + expect_error(fun() -> beam_clean:module(CleanInput, []) end), %% beam_peep PeepInput = {?MODULE,[{foo,0}],[], @@ -251,7 +261,7 @@ silly_coverage(Config) when is_list(Config) -> [{label,1}, {func_info,{atom,?MODULE},{atom,foo},0}, {label,2}|non_proper_list]}],99}, - ?line expect_error(fun() -> beam_peep:module(PeepInput, []) end), + expect_error(fun() -> beam_peep:module(PeepInput, []) end), %% beam_bsm. This is tricky. Our function must be sane enough to not crash %% btb_index/1, but must crash the main optimization pass. @@ -262,7 +272,7 @@ silly_coverage(Config) when is_list(Config) -> {label,2}, {test,bs_get_binary2,{f,99},0,[{x,0},{atom,all},1,[]],{x,0}}, {block,[a|b]}]}],0}, - ?line expect_error(fun() -> beam_bsm:module(BsmInput, []) end), + expect_error(fun() -> beam_bsm:module(BsmInput, []) end), %% beam_receive. ReceiveInput = {?MODULE,[{foo,0}],[], @@ -272,7 +282,7 @@ silly_coverage(Config) when is_list(Config) -> {label,2}, {call_ext,0,{extfunc,erlang,make_ref,0}}, {block,[a|b]}]}],0}, - ?line expect_error(fun() -> beam_receive:module(ReceiveInput, []) end), + expect_error(fun() -> beam_receive:module(ReceiveInput, []) end), BeamZInput = {?MODULE,[{foo,0}],[], [{function,foo,0,2, @@ -295,27 +305,30 @@ expect_error(Fun) -> try Fun() of Any -> io:format("~p", [Any]), - ?t:fail(call_was_supposed_to_fail) + ct:fail(call_was_supposed_to_fail) catch Class:Reason -> Stk = erlang:get_stacktrace(), io:format("~p:~p\n~p\n", [Class,Reason,Stk]), case {Class,Reason} of {error,undef} -> - ?t:fail(not_supposed_to_fail_with_undef); + ct:fail(not_supposed_to_fail_with_undef); {_,_} -> ok end end. confused_literals(Config) when is_list(Config) -> - ?line {0,infinity} = confused_literals_1(int), - ?line {0.0,infinity} = confused_literals_1(float), + {0,infinity} = confused_literals_1(int), + {0.0,infinity} = confused_literals_1(float), ok. confused_literals_1(int) -> {0,infinity}; confused_literals_1(float) -> {0.0,infinity}. +integer_encoding() -> + [{timetrap,{minutes,4}}]. + integer_encoding(Config) when is_list(Config) -> case ?MODULE of misc_SUITE -> integer_encoding_1(Config); @@ -323,22 +336,21 @@ integer_encoding(Config) when is_list(Config) -> end. integer_encoding_1(Config) -> - Dog = test_server:timetrap(?t:minutes(4)), - ?line PrivDir = ?config(priv_dir, Config), - ?line SrcFile = filename:join(PrivDir, "misc_SUITE_integer_encoding.erl"), - ?line DataFile = filename:join(PrivDir, "integer_encoding.data"), + PrivDir = proplists:get_value(priv_dir, Config), + SrcFile = filename:join(PrivDir, "misc_SUITE_integer_encoding.erl"), + DataFile = filename:join(PrivDir, "integer_encoding.data"), Mod = misc_SUITE_integer_encoding, %% Create files. - ?line {ok,Src} = file:open(SrcFile, [write]), - ?line {ok,Data} = file:open(DataFile, [write]), + {ok,Src} = file:open(SrcFile, [write]), + {ok,Data} = file:open(DataFile, [write]), io:format(Src, "-module(~s).\n", [Mod]), io:put_chars(Src, "-export([t/1]).\n"), io:put_chars(Src, "t(Last) ->[\n"), io:put_chars(Data, "[\n"), - ?line do_integer_encoding(-(id(1) bsl 10000), Src, Data), - ?line do_integer_encoding(id(1) bsl 10000, Src, Data), + do_integer_encoding(-(id(1) bsl 10000), Src, Data), + do_integer_encoding(id(1) bsl 10000, Src, Data), do_integer_encoding(1024, 0, Src, Data), _ = [begin B = 1 bsl I, @@ -350,32 +362,31 @@ integer_encoding_1(Config) -> do_integer_encoding(B+1, Src, Data) end || I <- lists:seq(1, 128)], io:put_chars(Src, "Last].\n\n"), - ?line ok = file:close(Src), + ok = file:close(Src), io:put_chars(Data, "0].\n\n"), - ?line ok = file:close(Data), + ok = file:close(Data), %% Compile and load Erlang module. - ?line SrcRoot = filename:rootname(SrcFile), - ?line {ok,Mod,Binary} = compile:file(SrcRoot, [binary,report]), - ?line {module,Mod} = code:load_binary(Mod, SrcRoot, Binary), + SrcRoot = filename:rootname(SrcFile), + {ok,Mod,Binary} = compile:file(SrcRoot, [binary,report]), + {module,Mod} = code:load_binary(Mod, SrcRoot, Binary), %% Compare lists. - ?line List = Mod:t(0), - ?line {ok,[List]} = file:consult(DataFile), + List = Mod:t(0), + {ok,[List]} = file:consult(DataFile), OneBsl10000 = id(1) bsl 10000, - ?line [-(1 bsl 10000),OneBsl10000|_] = List, + [-(1 bsl 10000),OneBsl10000|_] = List, %% Cleanup. - ?line file:delete(SrcFile), - ?line file:delete(DataFile), - ?t:timetrap_cancel(Dog), + file:delete(SrcFile), + file:delete(DataFile), ok. do_integer_encoding(0, _, _, _) -> ok; do_integer_encoding(N, I0, Src, Data) -> - I1 = (I0 bsl 5) bor (random:uniform(32) - 1), + I1 = (I0 bsl 5) bor (rand:uniform(32) - 1), do_integer_encoding(I1, Src, Data), - I2 = -(I1 bxor (random:uniform(32) - 1)), + I2 = -(I1 bxor (rand:uniform(32) - 1)), do_integer_encoding(I2, Src, Data), do_integer_encoding(N-1, I1, Src, Data). diff --git a/lib/compiler/test/num_bif_SUITE.erl b/lib/compiler/test/num_bif_SUITE.erl index d54fa203f0..78f6fdc3c7 100644 --- a/lib/compiler/test/num_bif_SUITE.erl +++ b/lib/compiler/test/num_bif_SUITE.erl @@ -19,7 +19,7 @@ %% -module(num_bif_SUITE). --include_lib("test_server/include/test_server.hrl"). +-include_lib("common_test/include/ct.hrl"). %% Tests optimization of the BIFs: %% abs/1 @@ -65,68 +65,68 @@ end_per_group(_GroupName, Config) -> t_abs(Config) when is_list(Config) -> %% Floats. - ?line 5.5 = abs(5.5), - ?line 0.0 = abs(0.0), - ?line 100.0 = abs(-100.0), + 5.5 = abs(5.5), + 0.0 = abs(0.0), + 100.0 = abs(-100.0), %% Integers. - ?line 5 = abs(5), - ?line 0 = abs(0), - ?line 100 = abs(-100), + 5 = abs(5), + 0 = abs(0), + 100 = abs(-100), %% The largest smallnum. OTP-3190. - ?line X = (1 bsl 27) - 1, - ?line X = abs(X), - ?line X = abs(X-1)+1, - ?line X = abs(X+1)-1, - ?line X = abs(-X), - ?line X = abs(-X-1)-1, - ?line X = abs(-X+1)+1, + X = (1 bsl 27) - 1, + X = abs(X), + X = abs(X-1)+1, + X = abs(X+1)-1, + X = abs(-X), + X = abs(-X-1)-1, + X = abs(-X+1)+1, %% Bignums. BigNum = 13984792374983749, - ?line BigNum = abs(BigNum), - ?line BigNum = abs(-BigNum), + BigNum = abs(BigNum), + BigNum = abs(-BigNum), ok. t_float(Config) when is_list(Config) -> - ?line 0.0 = float(0), - ?line 2.5 = float(2.5), - ?line 0.0 = float(0.0), - ?line -100.55 = float(-100.55), - ?line 42.0 = float(42), - ?line -100.0 = float(-100), + 0.0 = float(0), + 2.5 = float(2.5), + 0.0 = float(0.0), + -100.55 = float(-100.55), + 42.0 = float(42), + -100.0 = float(-100), %% Bignums. - ?line 4294967305.0 = float(4294967305), - ?line -4294967305.0 = float(-4294967305), + 4294967305.0 = float(4294967305), + -4294967305.0 = float(-4294967305), %% Extremly big bignums. - ?line Big = list_to_integer(lists:duplicate(2000, $1)), - ?line {'EXIT', {badarg, _}} = (catch float(Big)), + Big = list_to_integer(lists:duplicate(2000, $1)), + {'EXIT', {badarg, _}} = (catch float(Big)), %% Invalid types and lists. - ?line {'EXIT', {badarg, _}} = (catch list_to_integer(atom)), - ?line {'EXIT', {badarg, _}} = (catch list_to_integer(123)), - ?line {'EXIT', {badarg, _}} = (catch list_to_integer([$1, [$2]])), - ?line {'EXIT', {badarg, _}} = (catch list_to_integer("1.2")), - ?line {'EXIT', {badarg, _}} = (catch list_to_integer("a")), - ?line {'EXIT', {badarg, _}} = (catch list_to_integer("")), + {'EXIT', {badarg, _}} = (catch list_to_integer(atom)), + {'EXIT', {badarg, _}} = (catch list_to_integer(123)), + {'EXIT', {badarg, _}} = (catch list_to_integer([$1, [$2]])), + {'EXIT', {badarg, _}} = (catch list_to_integer("1.2")), + {'EXIT', {badarg, _}} = (catch list_to_integer("a")), + {'EXIT', {badarg, _}} = (catch list_to_integer("")), ok. %% Tests float_to_list/1. t_float_to_list(Config) when is_list(Config) -> - ?line test_ftl("0.0e+0", 0.0), - ?line test_ftl("2.5e+1", 25.0), - ?line test_ftl("2.5e+0", 2.5), - ?line test_ftl("2.5e-1", 0.25), - ?line test_ftl("-3.5e+17", -350.0e15), + test_ftl("0.0e+0", 0.0), + test_ftl("2.5e+1", 25.0), + test_ftl("2.5e+0", 2.5), + test_ftl("2.5e-1", 0.25), + test_ftl("-3.5e+17", -350.0e15), ok. test_ftl(Expect, Float) -> - %% No ?line on the next line -- we want the line number from t_float_to_list. + %% No on the next line -- we want the line number from t_float_to_list. Expect = remove_zeros(lists:reverse(float_to_list(Float)), []). %% Removes any non-significant zeros in a floating point number. @@ -148,36 +148,36 @@ remove_zeros([], Result) -> %% Tests integer_to_list/1. t_integer_to_list(Config) when is_list(Config) -> - ?line "0" = integer_to_list(0), - ?line "42" = integer_to_list(42), - ?line "-42" = integer_to_list(-42), - ?line "-42" = integer_to_list(-42), - ?line "32768" = integer_to_list(32768), - ?line "268435455" = integer_to_list(268435455), - ?line "-268435455" = integer_to_list(-268435455), - ?line "123456932798748738738" = integer_to_list(123456932798748738738), - ?line Big_List = lists:duplicate(2000, $1), - ?line Big = list_to_integer(Big_List), - ?line Big_List = integer_to_list(Big), + "0" = integer_to_list(0), + "42" = integer_to_list(42), + "-42" = integer_to_list(-42), + "-42" = integer_to_list(-42), + "32768" = integer_to_list(32768), + "268435455" = integer_to_list(268435455), + "-268435455" = integer_to_list(-268435455), + "123456932798748738738" = integer_to_list(123456932798748738738), + Big_List = lists:duplicate(2000, $1), + Big = list_to_integer(Big_List), + Big_List = integer_to_list(Big), ok. %% Tests list_to_float/1. t_list_to_float_safe(Config) when is_list(Config) -> - ?line 0.0 = list_to_float("0.0"), - ?line 0.0 = list_to_float("-0.0"), - ?line 0.5 = list_to_float("0.5"), - ?line -0.5 = list_to_float("-0.5"), - ?line 100.0 = list_to_float("1.0e2"), - ?line 127.5 = list_to_float("127.5"), - ?line -199.5 = list_to_float("-199.5"), - - ?line {'EXIT', {badarg, _}} = (catch list_to_float("0")), - ?line {'EXIT', {badarg, _}} = (catch list_to_float("0..0")), - ?line {'EXIT', {badarg, _}} = (catch list_to_float("0e12")), - ?line {'EXIT', {badarg, _}} = (catch list_to_float("--0.0")), -%% ?line {'EXIT', {badarg, _}} = (catch list_to_float("0.0e+99999999")), + 0.0 = list_to_float("0.0"), + 0.0 = list_to_float("-0.0"), + 0.5 = list_to_float("0.5"), + -0.5 = list_to_float("-0.5"), + 100.0 = list_to_float("1.0e2"), + 127.5 = list_to_float("127.5"), + -199.5 = list_to_float("-199.5"), + + {'EXIT', {badarg, _}} = (catch list_to_float("0")), + {'EXIT', {badarg, _}} = (catch list_to_float("0..0")), + {'EXIT', {badarg, _}} = (catch list_to_float("0e12")), + {'EXIT', {badarg, _}} = (catch list_to_float("--0.0")), +%% {'EXIT', {badarg, _}} = (catch list_to_float("0.0e+99999999")), ok. @@ -185,101 +185,101 @@ t_list_to_float_safe(Config) when is_list(Config) -> %% (Known to crash the Unix version of Erlang 4.4.1) t_list_to_float_risky(Config) when is_list(Config) -> - ?line Many_Ones = lists:duplicate(25000, $1), - ?line _ = list_to_float("2."++Many_Ones), - ?line {'EXIT', {badarg, _}} = (catch list_to_float("2"++Many_Ones)), + Many_Ones = lists:duplicate(25000, $1), + _ = list_to_float("2."++Many_Ones), + {'EXIT', {badarg, _}} = (catch list_to_float("2"++Many_Ones)), ok. %% Tests list_to_integer/1. t_list_to_integer(Config) when is_list(Config) -> - ?line 0 = list_to_integer("0"), - ?line 0 = list_to_integer("00"), - ?line 0 = list_to_integer("-0"), - ?line 1 = list_to_integer("1"), - ?line -1 = list_to_integer("-1"), - ?line 42 = list_to_integer("42"), - ?line -12 = list_to_integer("-12"), - ?line 32768 = list_to_integer("32768"), - ?line 268435455 = list_to_integer("268435455"), - ?line -268435455 = list_to_integer("-268435455"), + 0 = list_to_integer("0"), + 0 = list_to_integer("00"), + 0 = list_to_integer("-0"), + 1 = list_to_integer("1"), + -1 = list_to_integer("-1"), + 42 = list_to_integer("42"), + -12 = list_to_integer("-12"), + 32768 = list_to_integer("32768"), + 268435455 = list_to_integer("268435455"), + -268435455 = list_to_integer("-268435455"), %% Bignums. - ?line 123456932798748738738 = list_to_integer("123456932798748738738"), - ?line _ = list_to_integer(lists:duplicate(2000, $1)), + 123456932798748738738 = list_to_integer("123456932798748738738"), + _ = list_to_integer(lists:duplicate(2000, $1)), ok. %% Tests round/1. t_round(Config) when is_list(Config) -> - ?line 0 = round(0.0), - ?line 0 = round(0.4), - ?line 1 = round(0.5), - ?line 0 = round(-0.4), - ?line -1 = round(-0.5), - ?line 255 = round(255.3), - ?line 256 = round(255.6), - ?line -1033 = round(-1033.3), - ?line -1034 = round(-1033.6), + 0 = round(0.0), + 0 = round(0.4), + 1 = round(0.5), + 0 = round(-0.4), + -1 = round(-0.5), + 255 = round(255.3), + 256 = round(255.6), + -1033 = round(-1033.3), + -1034 = round(-1033.6), % OTP-3722: - ?line X = (1 bsl 27) - 1, - ?line MX = -X, - ?line MXm1 = -X-1, - ?line MXp1 = -X+1, - ?line F = X + 0.0, - ?line X = round(F), - ?line X = round(F+1)-1, - ?line X = round(F-1)+1, - ?line MX = round(-F), - ?line MXm1 = round(-F-1), - ?line MXp1 = round(-F+1), - - ?line X = round(F+0.1), - ?line X = round(F+1+0.1)-1, - ?line X = round(F-1+0.1)+1, - ?line MX = round(-F+0.1), - ?line MXm1 = round(-F-1+0.1), - ?line MXp1 = round(-F+1+0.1), - - ?line X = round(F-0.1), - ?line X = round(F+1-0.1)-1, - ?line X = round(F-1-0.1)+1, - ?line MX = round(-F-0.1), - ?line MXm1 = round(-F-1-0.1), - ?line MXp1 = round(-F+1-0.1), - - ?line 0.5 = abs(round(F+0.5)-(F+0.5)), - ?line 0.5 = abs(round(F-0.5)-(F-0.5)), - ?line 0.5 = abs(round(-F-0.5)-(-F-0.5)), - ?line 0.5 = abs(round(-F+0.5)-(-F+0.5)), + X = (1 bsl 27) - 1, + MX = -X, + MXm1 = -X-1, + MXp1 = -X+1, + F = X + 0.0, + X = round(F), + X = round(F+1)-1, + X = round(F-1)+1, + MX = round(-F), + MXm1 = round(-F-1), + MXp1 = round(-F+1), + + X = round(F+0.1), + X = round(F+1+0.1)-1, + X = round(F-1+0.1)+1, + MX = round(-F+0.1), + MXm1 = round(-F-1+0.1), + MXp1 = round(-F+1+0.1), + + X = round(F-0.1), + X = round(F+1-0.1)-1, + X = round(F-1-0.1)+1, + MX = round(-F-0.1), + MXm1 = round(-F-1-0.1), + MXp1 = round(-F+1-0.1), + + 0.5 = abs(round(F+0.5)-(F+0.5)), + 0.5 = abs(round(F-0.5)-(F-0.5)), + 0.5 = abs(round(-F-0.5)-(-F-0.5)), + 0.5 = abs(round(-F+0.5)-(-F+0.5)), %% Bignums. - ?line 4294967296 = round(4294967296.1), - ?line 4294967297 = round(4294967296.9), - ?line -4294967296 = -round(4294967296.1), - ?line -4294967297 = -round(4294967296.9), + 4294967296 = round(4294967296.1), + 4294967297 = round(4294967296.9), + -4294967296 = -round(4294967296.1), + -4294967297 = -round(4294967296.9), ok. t_trunc(Config) when is_list(Config) -> - ?line 0 = trunc(0.0), - ?line 5 = trunc(5.3333), - ?line -10 = trunc(-10.978987), + 0 = trunc(0.0), + 5 = trunc(5.3333), + -10 = trunc(-10.978987), % The largest smallnum, converted to float (OTP-3722): - ?line X = (1 bsl 27) - 1, - ?line F = X + 0.0, + X = (1 bsl 27) - 1, + F = X + 0.0, io:format("X = ~p/~w/~w, F = ~p/~w/~w, trunc(F) = ~p/~w/~w~n", [X, X, binary_to_list(term_to_binary(X)), F, F, binary_to_list(term_to_binary(F)), trunc(F), trunc(F), binary_to_list(term_to_binary(trunc(F)))]), - ?line X = trunc(F), - ?line X = trunc(F+1)-1, - ?line X = trunc(F-1)+1, - ?line X = -trunc(-F), - ?line X = -trunc(-F-1)-1, - ?line X = -trunc(-F+1)+1, + X = trunc(F), + X = trunc(F+1)-1, + X = trunc(F-1)+1, + X = -trunc(-F), + X = -trunc(-F-1)-1, + X = -trunc(-F+1)+1, %% Bignums. - ?line 4294967305 = trunc(4294967305.7), - ?line -4294967305 = trunc(-4294967305.7), + 4294967305 = trunc(4294967305.7), + -4294967305 = trunc(-4294967305.7), ok. diff --git a/lib/compiler/test/receive_SUITE.erl b/lib/compiler/test/receive_SUITE.erl index 4016fac0b5..8d2c78aae2 100644 --- a/lib/compiler/test/receive_SUITE.erl +++ b/lib/compiler/test/receive_SUITE.erl @@ -27,18 +27,17 @@ export/1,recv/1,coverage/1,otp_7980/1,ref_opt/1, wait/1]). --include_lib("test_server/include/test_server.hrl"). +-include_lib("common_test/include/ct.hrl"). init_per_testcase(_Case, Config) -> - ?line Dog = test_server:timetrap(test_server:minutes(2)), - [{watchdog, Dog}|Config]. + Config. -end_per_testcase(_Case, Config) -> - Dog=?config(watchdog, Config), - test_server:timetrap_cancel(Dog), +end_per_testcase(_Case, _Config) -> ok. -suite() -> [{ct_hooks,[ts_install_cth]}]. +suite() -> + [{ct_hooks,[ts_install_cth]}, + {timetrap,{minutes,2}}]. all() -> test_lib:recompile(?MODULE), @@ -64,21 +63,21 @@ end_per_group(_GroupName, Config) -> -record(state, {ena = true}). recv(Config) when is_list(Config) -> - ?line Pid = spawn_link(fun() -> loop(#state{}) end), + Pid = spawn_link(fun() -> loop(#state{}) end), Self = self(), - ?line Pid ! {Self,test}, + Pid ! {Self,test}, receive {ok,test} -> ok; {error,Other} -> io:format("Got unpexected ~p", [Other]), - ?line ?t:fail() + ct:fail(unexpected) after 10000 -> - ?line ?t:fail(no_answer) + ct:fail(no_answer) end, receive X -> io:format("Unexpected extra message: ~p", [X]), - ?line ?t:fail() + ct:fail(unexpected) after 10 -> ok end, @@ -116,9 +115,9 @@ coverage(Config) when is_list(Config) -> self() ! 17, self() ! 19, - ?line 59 = tuple_to_values(infinity, x), - ?line 61 = tuple_to_values(999999, x), - ?line 0 = tuple_to_values(1, x), + 59 = tuple_to_values(infinity, x), + 61 = tuple_to_values(999999, x), + 0 = tuple_to_values(1, x), ok. receive_all() -> @@ -188,8 +187,8 @@ ref_opt(Config) when is_list(Config) -> end. ref_opt_1(Config) -> - DataDir = ?config(data_dir, Config), - PrivDir = ?config(priv_dir, Config), + DataDir = proplists:get_value(data_dir, Config), + PrivDir = proplists:get_value(priv_dir, Config), Sources = filelib:wildcard(filename:join([DataDir,"ref_opt","*.{erl,S}"])), test_lib:p_run(fun(Src) -> do_ref_opt(Src, PrivDir) @@ -257,9 +256,9 @@ cover_recv_instructions() -> export(Config) when is_list(Config) -> Ref = make_ref(), - ?line self() ! {result,Ref,42}, - ?line 42 = export_1(Ref), - ?line {error,timeout} = export_1(Ref), + self() ! {result,Ref,42}, + 42 = export_1(Ref), + {error,timeout} = export_1(Ref), ok. export_1(Reference) -> diff --git a/lib/compiler/test/record_SUITE.erl b/lib/compiler/test/record_SUITE.erl index 2ef379e43f..680bd38317 100644 --- a/lib/compiler/test/record_SUITE.erl +++ b/lib/compiler/test/record_SUITE.erl @@ -21,7 +21,7 @@ -module(record_SUITE). --include_lib("test_server/include/test_server.hrl"). +-include_lib("common_test/include/ct.hrl"). -export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, init_per_group/2,end_per_group/2, @@ -31,15 +31,14 @@ nested_access/1,coverage/1]). init_per_testcase(_Case, Config) -> - ?line Dog = test_server:timetrap(test_server:minutes(2)), - [{watchdog,Dog}|Config]. + Config. -end_per_testcase(_Case, Config) -> - Dog = ?config(watchdog, Config), - test_server:timetrap_cancel(Dog), +end_per_testcase(_Case, _Config) -> ok. -suite() -> [{ct_hooks,[ts_install_cth]}]. +suite() -> + [{ct_hooks,[ts_install_cth]}, + {timetrap,{minutes,2}}]. all() -> test_lib:recompile(?MODULE), @@ -71,18 +70,18 @@ end_per_group(_GroupName, Config) -> errors(Config) when is_list(Config) -> Foo = #foo{a=1,b=2,c=3,d=4}, - ?line #foo{a=19,b=42,c=3,d=4} = update_foo(Foo, 19, 42), - - ?line {'EXIT',{{badrecord,bar},_}} = (catch update_foo_bar(Foo, 19)), - ?line {'EXIT',{{badrecord,bar},_}} = (catch update_foo_bar(Foo, 19, 35)), - ?line {'EXIT',{{badrecord,bar},_}} = (catch update_foo_bar(Foo, 19, 35, 17)), - ?line {'EXIT',{{badrecord,bar},_}} = (catch update_foo_bar(Foo, 19, 35, 17, 42)), - - ?line {'EXIT',{{badrecord,barf},_}} = (catch update_foo_barf(Foo, 19)), - ?line {'EXIT',{{badrecord,barf},_}} = (catch update_foo_barf(Foo, 19, 35)), - ?line {'EXIT',{{badrecord,barf},_}} = (catch update_foo_barf(Foo, 19, 35, 17)), - ?line {'EXIT',{{badrecord,barf},_}} = (catch update_foo_barf(Foo, 19, 35, 17, 42)), - ?line {'EXIT',{{badrecord,barf},_}} = (catch update_foo_barf(Foo, 19, + #foo{a=19,b=42,c=3,d=4} = update_foo(Foo, 19, 42), + + {'EXIT',{{badrecord,bar},_}} = (catch update_foo_bar(Foo, 19)), + {'EXIT',{{badrecord,bar},_}} = (catch update_foo_bar(Foo, 19, 35)), + {'EXIT',{{badrecord,bar},_}} = (catch update_foo_bar(Foo, 19, 35, 17)), + {'EXIT',{{badrecord,bar},_}} = (catch update_foo_bar(Foo, 19, 35, 17, 42)), + + {'EXIT',{{badrecord,barf},_}} = (catch update_foo_barf(Foo, 19)), + {'EXIT',{{badrecord,barf},_}} = (catch update_foo_barf(Foo, 19, 35)), + {'EXIT',{{badrecord,barf},_}} = (catch update_foo_barf(Foo, 19, 35, 17)), + {'EXIT',{{badrecord,barf},_}} = (catch update_foo_barf(Foo, 19, 35, 17, 42)), + {'EXIT',{{badrecord,barf},_}} = (catch update_foo_barf(Foo, 19, 35, 17, 42, -2)), ok. @@ -118,72 +117,72 @@ update_foo_barf(#foo{}=R, A, _B, C, D, E) -> R#barf{a=A,b=A,c=C,d=D,e=E}. --define(TrueGuard(Expr), if Expr -> ok; true -> ?t:fail() end). --define(FalseGuard(Expr), if Expr -> ?t:fail(); true -> ok end). +-define(TrueGuard(Expr), if Expr -> ok; true -> ct:fail(failed) end). +-define(FalseGuard(Expr), if Expr -> ct:fail(failed); true -> ok end). record_test_2(Config) when is_list(Config) -> - ?line true = is_record(#foo{}, foo), - ?line false = is_record(#foo{}, barf), - ?line false = is_record({foo}, foo), + true = is_record(#foo{}, foo), + false = is_record(#foo{}, barf), + false = is_record({foo}, foo), - ?line true = erlang:is_record(#foo{}, foo), - ?line false = erlang:is_record(#foo{}, barf), - ?line false = erlang:is_record({foo}, foo), + true = erlang:is_record(#foo{}, foo), + false = erlang:is_record(#foo{}, barf), + false = erlang:is_record({foo}, foo), - ?line false = is_record([], foo), - ?line false = is_record(Config, foo), + false = is_record([], foo), + false = is_record(Config, foo), - ?line ?TrueGuard(is_record(#foo{}, foo)), - ?line ?FalseGuard(is_record(#foo{}, barf)), - ?line ?FalseGuard(is_record({foo}, foo)), + ?TrueGuard(is_record(#foo{}, foo)), + ?FalseGuard(is_record(#foo{}, barf)), + ?FalseGuard(is_record({foo}, foo)), - ?line ?TrueGuard(erlang:is_record(#foo{}, foo)), - ?line ?FalseGuard(erlang:is_record(#foo{}, barf)), - ?line ?FalseGuard(erlang:is_record({foo}, foo)), + ?TrueGuard(erlang:is_record(#foo{}, foo)), + ?FalseGuard(erlang:is_record(#foo{}, barf)), + ?FalseGuard(erlang:is_record({foo}, foo)), - ?line ?FalseGuard(is_record([], foo)), - ?line ?FalseGuard(is_record(Config, foo)), + ?FalseGuard(is_record([], foo)), + ?FalseGuard(is_record(Config, foo)), %% 'not is_record/2' to test guard optimization. - ?line ?FalseGuard(not is_record(#foo{}, foo)), - ?line ?TrueGuard(not is_record(#foo{}, barf)), - ?line ?TrueGuard(not is_record({foo}, foo)), + ?FalseGuard(not is_record(#foo{}, foo)), + ?TrueGuard(not is_record(#foo{}, barf)), + ?TrueGuard(not is_record({foo}, foo)), - ?line ?FalseGuard(not erlang:is_record(#foo{}, foo)), - ?line ?TrueGuard(not erlang:is_record(#foo{}, barf)), - ?line ?TrueGuard(not erlang:is_record({foo}, foo)), + ?FalseGuard(not erlang:is_record(#foo{}, foo)), + ?TrueGuard(not erlang:is_record(#foo{}, barf)), + ?TrueGuard(not erlang:is_record({foo}, foo)), Foo = id(#foo{}), - ?line ?FalseGuard(not erlang:is_record(Foo, foo)), - ?line ?TrueGuard(not erlang:is_record(Foo, barf)), + ?FalseGuard(not erlang:is_record(Foo, foo)), + ?TrueGuard(not erlang:is_record(Foo, barf)), - ?line ?TrueGuard(not is_record(Config, foo)), + ?TrueGuard(not is_record(Config, foo)), - ?line ?TrueGuard(not is_record(a, foo)), - ?line ?TrueGuard(not is_record([], foo)), + ?TrueGuard(not is_record(a, foo)), + ?TrueGuard(not is_record([], foo)), %% Pass non-literal first argument. - ?line true = is_record(id(#foo{}), foo), - ?line false = is_record(id(#foo{}), barf), - ?line false = is_record(id({foo}), foo), + true = is_record(id(#foo{}), foo), + false = is_record(id(#foo{}), barf), + false = is_record(id({foo}), foo), - ?line true = erlang:is_record(id(#foo{}), foo), - ?line false = erlang:is_record(id(#foo{}), barf), - ?line false = erlang:is_record(id({foo}), foo), + true = erlang:is_record(id(#foo{}), foo), + false = erlang:is_record(id(#foo{}), barf), + false = erlang:is_record(id({foo}), foo), NoRec1 = id(blurf), NoRec2 = id([]), - ?line ?TrueGuard(not is_record(NoRec1, foo)), - ?line ?TrueGuard(not is_record(NoRec2, foo)), + ?TrueGuard(not is_record(NoRec1, foo)), + ?TrueGuard(not is_record(NoRec2, foo)), %% The optimizer attempts to move expressions to guards, %% but it must not move an is_record/2 call that is not %% allowed in a guard in the first place. - ?line ok = case is_record(id({a}), id(a)) of + ok = case is_record(id({a}), id(a)) of true -> ok; false -> error end, @@ -191,61 +190,61 @@ record_test_2(Config) when is_list(Config) -> %% Force the use of guard bifs by using the 'xor' operation. False = id(false), - ?line ?TrueGuard(is_record(#foo{}, foo) xor False), - ?line ?FalseGuard(is_record(#foo{}, barf) xor False), - ?line ?FalseGuard(is_record({foo}, foo) xor False ), + ?TrueGuard(is_record(#foo{}, foo) xor False), + ?FalseGuard(is_record(#foo{}, barf) xor False), + ?FalseGuard(is_record({foo}, foo) xor False ), - ?line ?TrueGuard(is_record(Foo, foo) xor False), - ?line ?FalseGuard(is_record(Foo, barf) xor False), + ?TrueGuard(is_record(Foo, foo) xor False), + ?FalseGuard(is_record(Foo, barf) xor False), %% Implicit guards by using a list comprehension. List = id([1,#foo{a=2},3,#bar{d=4},5,#foo{a=6},7]), - ?line [#foo{a=2},#foo{a=6}] = [X || X <- List, is_record(X, foo)], - ?line [#bar{d=4}] = [X || X <- List, is_record(X, bar)], - ?line [1,#foo{a=2},3,5,#foo{a=6},7] = + [#foo{a=2},#foo{a=6}] = [X || X <- List, is_record(X, foo)], + [#bar{d=4}] = [X || X <- List, is_record(X, bar)], + [1,#foo{a=2},3,5,#foo{a=6},7] = [X || X <- List, not is_record(X, bar)], - ?line [1,3,5,7] = + [1,3,5,7] = [X || X <- List, ((not is_record(X, bar)) and (not is_record(X, foo)))], - ?line [#foo{a=2},#bar{d=4},#foo{a=6}] = + [#foo{a=2},#bar{d=4},#foo{a=6}] = [X || X <- List, ((is_record(X, bar)) or (is_record(X, foo)))], - ?line [1,3,#bar{d=4}] = + [1,3,#bar{d=4}] = [X || X <- List, ((is_record(X, bar)) or (X < 5))], - ?line MyList = [#foo{a=3},x,[],{a,b}], - ?line [#foo{a=3}] = [X || X <- MyList, is_record(X, foo)], - ?line [x,[],{a,b}] = [X || X <- MyList, not is_record(X, foo)], - ?line [#foo{a=3}] = [X || X <- MyList, begin is_record(X, foo) end], - ?line [x,[],{a,b}] = [X || X <- MyList, begin not is_record(X, foo) end], - ?line [#foo{a=3},x,[],{a,b}] = [X || X <- MyList, is_record(X, foo) or - not is_binary(X)], - ?line [#foo{a=3},x,[],{a,b}] = [X || X <- MyList, not is_record(X, foo) or - not is_binary(X)], - ?line [#foo{a=3}] = [X || X <- MyList, is_record(X, foo) or is_reference(X)], - ?line [x,[],{a,b}] = [X || X <- MyList, not is_record(X, foo) or - is_reference(X)], - ?line [#foo{a=3},x,[],{a,b}] = [X || X <- MyList, - begin is_record(X, foo) or - not is_binary(X) end], - ?line [#foo{a=3},x,[],{a,b}] = [X || X <- MyList, - begin not is_record(X, foo) or - not is_binary(X) end], - ?line [#foo{a=3}] = [X || X <- MyList, - begin is_record(X, foo) or is_reference(X) end], - ?line [x,[],{a,b}] = [X || X <- MyList, - begin not is_record(X, foo) or - is_reference(X) end], + MyList = [#foo{a=3},x,[],{a,b}], + [#foo{a=3}] = [X || X <- MyList, is_record(X, foo)], + [x,[],{a,b}] = [X || X <- MyList, not is_record(X, foo)], + [#foo{a=3}] = [X || X <- MyList, begin is_record(X, foo) end], + [x,[],{a,b}] = [X || X <- MyList, begin not is_record(X, foo) end], + [#foo{a=3},x,[],{a,b}] = [X || X <- MyList, is_record(X, foo) or + not is_binary(X)], + [#foo{a=3},x,[],{a,b}] = [X || X <- MyList, not is_record(X, foo) or + not is_binary(X)], + [#foo{a=3}] = [X || X <- MyList, is_record(X, foo) or is_reference(X)], + [x,[],{a,b}] = [X || X <- MyList, not is_record(X, foo) or + is_reference(X)], + [#foo{a=3},x,[],{a,b}] = [X || X <- MyList, + begin is_record(X, foo) or + not is_binary(X) end], + [#foo{a=3},x,[],{a,b}] = [X || X <- MyList, + begin not is_record(X, foo) or + not is_binary(X) end], + [#foo{a=3}] = [X || X <- MyList, + begin is_record(X, foo) or is_reference(X) end], + [x,[],{a,b}] = [X || X <- MyList, + begin not is_record(X, foo) or + is_reference(X) end], %% Call is_record/2 with illegal arguments. - ?line [] = [X || X <- [], is_record(t, id(X))], - ?line {'EXIT',{badarg,_}} = (catch [X || X <- [1], is_record(t, id(X))]), + [] = [X || X <- [], is_record(t, id(X))], + {'EXIT',{badarg,_}} = (catch [X || X <- [1], is_record(t, id(X))]), %% Update several fields with a string literal. - ?line #barf{} = Barf0 = id(#barf{}), - ?line Barf = update_barf(Barf0), - ?line #barf{a="abc",b=1} = id(Barf), + #barf{} = Barf0 = id(#barf{}), + Barf = update_barf(Barf0), + #barf{a="abc",b=1} = id(Barf), %% Test optimization of is_record/3. false = case id({a,b}) of @@ -258,125 +257,125 @@ record_test_2(Config) when is_list(Config) -> ok. record_test_3(Config) when is_list(Config) -> - ?line true = is_record(#foo{}, foo, 5), - ?line false = is_record(#foo{}, barf, 5), - ?line false = is_record(#foo{}, barf, 6), - ?line false = is_record({foo}, foo, 5), + true = is_record(#foo{}, foo, 5), + false = is_record(#foo{}, barf, 5), + false = is_record(#foo{}, barf, 6), + false = is_record({foo}, foo, 5), - ?line true = erlang:is_record(#foo{}, foo, 5), - ?line false = erlang:is_record(#foo{}, barf, 5), - ?line false = erlang:is_record({foo}, foo, 5), + true = erlang:is_record(#foo{}, foo, 5), + false = erlang:is_record(#foo{}, barf, 5), + false = erlang:is_record({foo}, foo, 5), - ?line false = is_record([], foo), - ?line false = is_record(Config, foo), + false = is_record([], foo), + false = is_record(Config, foo), - ?line ?TrueGuard(is_record(#foo{}, foo, 5)), - ?line ?FalseGuard(is_record(#foo{}, barf, 5)), - ?line ?FalseGuard(is_record(#foo{}, barf, 6)), - ?line ?FalseGuard(is_record({foo}, foo, 5)), + ?TrueGuard(is_record(#foo{}, foo, 5)), + ?FalseGuard(is_record(#foo{}, barf, 5)), + ?FalseGuard(is_record(#foo{}, barf, 6)), + ?FalseGuard(is_record({foo}, foo, 5)), - ?line ?TrueGuard(erlang:is_record(#foo{}, foo, 5)), - ?line ?FalseGuard(erlang:is_record(#foo{}, barf, 5)), - ?line ?FalseGuard(erlang:is_record(#foo{}, barf, 6)), - ?line ?FalseGuard(erlang:is_record({foo}, foo, 5)), + ?TrueGuard(erlang:is_record(#foo{}, foo, 5)), + ?FalseGuard(erlang:is_record(#foo{}, barf, 5)), + ?FalseGuard(erlang:is_record(#foo{}, barf, 6)), + ?FalseGuard(erlang:is_record({foo}, foo, 5)), - ?line ?FalseGuard(is_record([], foo, 5)), - ?line ?FalseGuard(is_record(Config, foo, 5)), + ?FalseGuard(is_record([], foo, 5)), + ?FalseGuard(is_record(Config, foo, 5)), %% 'not is_record/2' to test guard optimization. - ?line ?FalseGuard(not is_record(#foo{}, foo, 5)), - ?line ?TrueGuard(not is_record(#foo{}, barf, 6)), - ?line ?TrueGuard(not is_record({foo}, foo, 5)), + ?FalseGuard(not is_record(#foo{}, foo, 5)), + ?TrueGuard(not is_record(#foo{}, barf, 6)), + ?TrueGuard(not is_record({foo}, foo, 5)), - ?line ?FalseGuard(not erlang:is_record(#foo{}, foo, 5)), - ?line ?TrueGuard(not erlang:is_record(#foo{}, barf, 5)), - ?line ?TrueGuard(not erlang:is_record({foo}, foo, 5)), + ?FalseGuard(not erlang:is_record(#foo{}, foo, 5)), + ?TrueGuard(not erlang:is_record(#foo{}, barf, 5)), + ?TrueGuard(not erlang:is_record({foo}, foo, 5)), Foo = id(#foo{}), - ?line ?FalseGuard(not erlang:is_record(Foo, foo, 5)), - ?line ?TrueGuard(not erlang:is_record(Foo, barf, 6)), + ?FalseGuard(not erlang:is_record(Foo, foo, 5)), + ?TrueGuard(not erlang:is_record(Foo, barf, 6)), - ?line ?TrueGuard(not is_record(Config, foo, 5)), + ?TrueGuard(not is_record(Config, foo, 5)), - ?line ?TrueGuard(not is_record(a, foo, 5)), - ?line ?TrueGuard(not is_record([], foo, 5)), + ?TrueGuard(not is_record(a, foo, 5)), + ?TrueGuard(not is_record([], foo, 5)), %% Pass non-literal first argument. - ?line true = is_record(id(#foo{}), foo, 5), - ?line false = is_record(id(#foo{}), barf, 6), - ?line false = is_record(id({foo}), foo, 5), + true = is_record(id(#foo{}), foo, 5), + false = is_record(id(#foo{}), barf, 6), + false = is_record(id({foo}), foo, 5), - ?line true = erlang:is_record(id(#foo{}), foo, 5), - ?line false = erlang:is_record(id(#foo{}), barf, 6), - ?line false = erlang:is_record(id({foo}), foo, 5), + true = erlang:is_record(id(#foo{}), foo, 5), + false = erlang:is_record(id(#foo{}), barf, 6), + false = erlang:is_record(id({foo}), foo, 5), NoRec1 = id(blurf), NoRec2 = id([]), - ?line ?TrueGuard(not is_record(NoRec1, foo, 5)), - ?line ?TrueGuard(not is_record(NoRec2, foo, 5)), + ?TrueGuard(not is_record(NoRec1, foo, 5)), + ?TrueGuard(not is_record(NoRec2, foo, 5)), %% Force the use of guard bifs by using the 'xor' operation. False = id(false), - ?line ?TrueGuard(is_record(#foo{}, foo, 5) xor False), - ?line ?FalseGuard(is_record(#foo{}, barf, 6) xor False), - ?line ?FalseGuard(is_record({foo}, foo, 5) xor False ), + ?TrueGuard(is_record(#foo{}, foo, 5) xor False), + ?FalseGuard(is_record(#foo{}, barf, 6) xor False), + ?FalseGuard(is_record({foo}, foo, 5) xor False ), - ?line ?TrueGuard(is_record(Foo, foo, 5) xor False), - ?line ?FalseGuard(is_record(Foo, barf, 6) xor False), + ?TrueGuard(is_record(Foo, foo, 5) xor False), + ?FalseGuard(is_record(Foo, barf, 6) xor False), %% Implicit guards by using a list comprehension. List = id([1,#foo{a=2},3,#bar{d=4},5,#foo{a=6},7]), - ?line [#foo{a=2},#foo{a=6}] = [X || X <- List, is_record(X, foo, 5)], - ?line [#bar{d=4}] = [X || X <- List, is_record(X, bar, 5)], - ?line [1,#foo{a=2},3,5,#foo{a=6},7] = + [#foo{a=2},#foo{a=6}] = [X || X <- List, is_record(X, foo, 5)], + [#bar{d=4}] = [X || X <- List, is_record(X, bar, 5)], + [1,#foo{a=2},3,5,#foo{a=6},7] = [X || X <- List, not is_record(X, bar, 5)], - ?line [1,3,5,7] = + [1,3,5,7] = [X || X <- List, ((not is_record(X, bar, 5)) and (not is_record(X, foo, 5)))], - ?line [#foo{a=2},#bar{d=4},#foo{a=6}] = + [#foo{a=2},#bar{d=4},#foo{a=6}] = [X || X <- List, ((is_record(X, bar, 5)) or (is_record(X, foo, 5)))], - ?line [1,3,#bar{d=4}] = + [1,3,#bar{d=4}] = [X || X <- List, ((is_record(X, bar, 5)) or (X < 5))], - ?line MyList = [#foo{a=3},x,[],{a,b}], - ?line [#foo{a=3}] = [X || X <- MyList, is_record(X, foo, 5)], - ?line [x,[],{a,b}] = [X || X <- MyList, not is_record(X, foo, 5)], - ?line [#foo{a=3}] = [X || X <- MyList, begin is_record(X, foo, 5) end], - ?line [x,[],{a,b}] = [X || X <- MyList, begin not is_record(X, foo, 5) end], - ?line [#foo{a=3},x,[],{a,b}] = [X || X <- MyList, is_record(X, foo, 5) or - not is_binary(X)], - ?line [#foo{a=3},x,[],{a,b}] = [X || X <- MyList, not is_record(X, foo, 5) or - not is_binary(X)], - ?line [#foo{a=3}] = [X || X <- MyList, is_record(X, foo) or is_reference(X)], - ?line [x,[],{a,b}] = [X || X <- MyList, not is_record(X, foo) or - is_reference(X)], - ?line [#foo{a=3},x,[],{a,b}] = [X || X <- MyList, - begin is_record(X, foo, 5) or - not is_binary(X) end], - ?line [#foo{a=3},x,[],{a,b}] = [X || X <- MyList, - begin not is_record(X, foo, 5) or - not is_binary(X) end], - ?line [#foo{a=3}] = [X || X <- MyList, - begin is_record(X, foo, 5) or is_reference(X) end], - ?line [x,[],{a,b}] = [X || X <- MyList, - begin not is_record(X, foo, 5) or - is_reference(X) end], + MyList = [#foo{a=3},x,[],{a,b}], + [#foo{a=3}] = [X || X <- MyList, is_record(X, foo, 5)], + [x,[],{a,b}] = [X || X <- MyList, not is_record(X, foo, 5)], + [#foo{a=3}] = [X || X <- MyList, begin is_record(X, foo, 5) end], + [x,[],{a,b}] = [X || X <- MyList, begin not is_record(X, foo, 5) end], + [#foo{a=3},x,[],{a,b}] = [X || X <- MyList, is_record(X, foo, 5) or + not is_binary(X)], + [#foo{a=3},x,[],{a,b}] = [X || X <- MyList, not is_record(X, foo, 5) or + not is_binary(X)], + [#foo{a=3}] = [X || X <- MyList, is_record(X, foo) or is_reference(X)], + [x,[],{a,b}] = [X || X <- MyList, not is_record(X, foo) or + is_reference(X)], + [#foo{a=3},x,[],{a,b}] = [X || X <- MyList, + begin is_record(X, foo, 5) or + not is_binary(X) end], + [#foo{a=3},x,[],{a,b}] = [X || X <- MyList, + begin not is_record(X, foo, 5) or + not is_binary(X) end], + [#foo{a=3}] = [X || X <- MyList, + begin is_record(X, foo, 5) or is_reference(X) end], + [x,[],{a,b}] = [X || X <- MyList, + begin not is_record(X, foo, 5) or + is_reference(X) end], %% Update several fields with a string literal. - ?line #barf{} = Barf0 = id(#barf{}), - ?line Barf = update_barf(Barf0), - ?line #barf{a="abc",b=1} = id(Barf), + #barf{} = Barf0 = id(#barf{}), + Barf = update_barf(Barf0), + #barf{a="abc",b=1} = id(Barf), %% Non-literal arguments. - ?line true = is_record(id(#barf{}), id(barf), id(6)), - ?line false = is_record(id(#barf{}), id(barf), id(42)), - ?line false = is_record(id(#barf{}), id(foo), id(6)), + true = is_record(id(#barf{}), id(barf), id(6)), + false = is_record(id(#barf{}), id(barf), id(42)), + false = is_record(id(#barf{}), id(foo), id(6)), Rec = id(#barf{}), Good = id(barf), @@ -389,15 +388,15 @@ record_test_3(Config) when is_list(Config) -> ok. record_access_in_guards(Config) when is_list(Config) -> - ?line Priv = ?config(priv_dir, Config), - ?line file:set_cwd(test_lib:get_data_dir(Config)), - ?line Opts0 = [{outdir,Priv},report_errors|test_lib:opt_opts(?MODULE)], + Priv = proplists:get_value(priv_dir, Config), + file:set_cwd(test_lib:get_data_dir(Config)), + Opts0 = [{outdir,Priv},report_errors|test_lib:opt_opts(?MODULE)], M = record_access_in_guards, Opts = [strict_record_tests|Opts0], - ?line io:format("Options: ~p\n", [Opts]), - ?line {ok,M} = c:c(M, Opts), - ?line ok = M:t(), + io:format("Options: ~p\n", [Opts]), + {ok,M} = c:c(M, Opts), + ok = M:t(), ok. @@ -487,19 +486,19 @@ update_barf(R) -> R#barf{a="abc",b=1}. eval_once(Config) when is_list(Config) -> - ?line once(fun(GetRec) -> + once(fun(GetRec) -> true = erlang:is_record(GetRec(), foo) end, #foo{}), - ?line once(fun(GetRec) -> + once(fun(GetRec) -> (GetRec())#foo{a=1} end, #foo{}), - ?line once(fun(GetRec) -> + once(fun(GetRec) -> (GetRec())#foo{a=1,b=2} end, #foo{}), - ?line once(fun(GetRec) -> + once(fun(GetRec) -> (GetRec())#foo{a=1,b=2,c=3} end, #foo{}), - ?line once(fun(GetRec) -> + once(fun(GetRec) -> (GetRec())#foo{a=1,b=2,c=3,d=4} end, #foo{}), ok. @@ -515,7 +514,7 @@ once(Test, Record) -> 1 -> ok; N -> io:format("Evaluated ~w times\n", [N]), - ?t:fail() + ct:fail(more_than_once) end, Result. @@ -571,21 +570,21 @@ nested_access(Config) when is_list(Config) -> N0 = #nrec0{}, N1 = #nrec1{}, N2 = #nrec2{}, - ?line <<"nested0">> = N0#nrec0.name, - ?line <<"nested1">> = N1#nrec1.name, - ?line <<"nested2">> = N2#nrec2.name, - ?line <<"nested0">> = N1#nrec1.nrec0#nrec0.name, - ?line <<"nested0">> = N2#nrec2.nrec1#nrec1.nrec0#nrec0.name, - ?line <<"nested1">> = N2#nrec2.nrec1#nrec1.name, - ?line <<"nested0">> = ((N2#nrec2.nrec1)#nrec1.nrec0)#nrec0.name, + <<"nested0">> = N0#nrec0.name, + <<"nested1">> = N1#nrec1.name, + <<"nested2">> = N2#nrec2.name, + <<"nested0">> = N1#nrec1.nrec0#nrec0.name, + <<"nested0">> = N2#nrec2.nrec1#nrec1.nrec0#nrec0.name, + <<"nested1">> = N2#nrec2.nrec1#nrec1.name, + <<"nested0">> = ((N2#nrec2.nrec1)#nrec1.nrec0)#nrec0.name, N1a = N2#nrec2.nrec1#nrec1{name = <<"nested1a">>}, - ?line <<"nested1a">> = N1a#nrec1.name, + <<"nested1a">> = N1a#nrec1.name, N2a = N2#nrec2.nrec1#nrec1.nrec0#nrec0{name = <<"nested0a">>}, N2b = ((N2#nrec2.nrec1)#nrec1.nrec0)#nrec0{name = <<"nested0a">>}, - ?line <<"nested0a">> = N2a#nrec0.name, - ?line N2a = N2b, + <<"nested0a">> = N2a#nrec0.name, + N2a = N2b, ok. -record(rr, {a,b,c}). diff --git a/lib/compiler/test/regressions_SUITE.erl b/lib/compiler/test/regressions_SUITE.erl index 716a9693ed..3fd4645529 100644 --- a/lib/compiler/test/regressions_SUITE.erl +++ b/lib/compiler/test/regressions_SUITE.erl @@ -19,28 +19,25 @@ %% Test specific code snippets that has crashed the compiler in the past. -module(regressions_SUITE). --include_lib("test_server/include/test_server.hrl"). - --export([all/0, groups/0, init_per_testcase/2,end_per_testcase/2]). +-include_lib("common_test/include/ct.hrl"). +-export([all/0,groups/0,init_per_testcase/2,end_per_testcase/2,suite/0]). -export([maps/1]). groups() -> [{p,test_lib:parallel(), [maps]}]. -% Default timetrap timeout (set in init_per_testcase). --define(default_timeout, ?t:minutes(2)). - init_per_testcase(_Case, Config) -> - ?line Dog = ?t:timetrap(?default_timeout), - [{watchdog, Dog} | Config]. + Config. -end_per_testcase(_Case, Config) -> - Dog = ?config(watchdog, Config), - test_server:timetrap_cancel(Dog), +end_per_testcase(_Case, _Config) -> ok. +suite() -> + [{ct_hooks,[ts_install_cth]}, + {timetrap,{minutes,2}}]. + all() -> test_lib:recompile(?MODULE), [{group,p}]. @@ -62,7 +59,8 @@ run(Config, Tests) -> io:format("Compiling test for: ~w~n", [N]), case catch run_test(Config, P) of {'EXIT', Reason} -> - ?t:format("~nTest ~p failed.~nReason: ~p~n", [N, Reason]), + io:format("~nTest ~p failed.~nReason: ~p~n", + [N, Reason]), fail(); _ -> ok end @@ -73,7 +71,7 @@ run(Config, Tests) -> run_test(Conf, Test0) -> Module = "regressions_"++test_lib:uniq(), Filename = Module ++ ".erl", - DataDir = ?config(priv_dir, Conf), + DataDir = proplists:get_value(priv_dir, Conf), Test = ["-module(", Module, "). ", Test0], File = filename:join(DataDir, Filename), Def = [binary,export_all,return], @@ -94,5 +92,4 @@ run_test(Conf, Test0) -> ok. fail() -> - io:format("failed~n"), - ?t:fail(). + ct:fail(failed). diff --git a/lib/compiler/test/test_lib.erl b/lib/compiler/test/test_lib.erl index 09ec8f3c81..3ca93fb021 100644 --- a/lib/compiler/test/test_lib.erl +++ b/lib/compiler/test/test_lib.erl @@ -19,7 +19,7 @@ %% -module(test_lib). --include_lib("test_server/include/test_server.hrl"). +-include_lib("common_test/include/ct.hrl"). -compile({no_auto_import,[binary_part/2]}). -export([id/1,recompile/1,parallel/0,uniq/0,opt_opts/1,get_data_dir/1, smoke_disasm/1,p_run/2,binary_part/2]). @@ -52,7 +52,7 @@ smoke_disasm(File) when is_list(File) -> %% be slower than running them sequentially. parallel() -> - case ?t:is_cover() orelse erlang:system_info(schedulers) =:= 1 of + case test_server:is_cover() orelse erlang:system_info(schedulers) =:= 1 of true -> []; false -> [parallel] end. @@ -66,7 +66,7 @@ uniq() -> opt_opts(Mod) -> Comp = Mod:module_info(compile), - {value,{options,Opts}} = lists:keysearch(options, 1, Comp), + {options,Opts} = lists:keyfind(options, 1, Comp), lists:filter(fun(no_copt) -> true; (no_postopt) -> true; (no_float_opt) -> true; @@ -85,7 +85,7 @@ opt_opts(Mod) -> %% This function retrieves the path to the original data directory. get_data_dir(Config) -> - Data0 = ?config(data_dir, Config), + Data0 = proplists:get_value(data_dir, Config), Opts = [{return,list}], Data1 = re:replace(Data0, "_no_opt_SUITE", "_SUITE", Opts), Data = re:replace(Data1, "_post_opt_SUITE", "_SUITE", Opts), @@ -96,7 +96,7 @@ get_data_dir(Config) -> p_run(Test, List) -> S = erlang:system_info(schedulers), - N = case ?t:is_cover() of + N = case test_server:is_cover() of false -> S + 1; true -> @@ -118,7 +118,8 @@ p_run_loop(_, [], _, [], Errors, Ws) -> 1 -> {comment,"1 warning"}; N -> {comment,integer_to_list(N)++" warnings"} end; - N -> ?t:fail({N,errors}) + N -> + ct:fail({N,errors}) end; p_run_loop(Test, [H|T], N, Refs, Errors, Ws) when length(Refs) < N -> {_,Ref} = erlang:spawn_monitor(fun() -> exit(Test(H)) end), diff --git a/lib/compiler/test/trycatch_SUITE.erl b/lib/compiler/test/trycatch_SUITE.erl index adcab8ef67..82e3c86649 100644 --- a/lib/compiler/test/trycatch_SUITE.erl +++ b/lib/compiler/test/trycatch_SUITE.erl @@ -28,7 +28,7 @@ plain_catch_coverage/1,andalso_orelse/1,get_in_try/1, hockey/1]). --include_lib("test_server/include/test_server.hrl"). +-include_lib("common_test/include/ct.hrl"). suite() -> [{ct_hooks,[ts_install_cth]}]. @@ -60,32 +60,32 @@ end_per_group(_GroupName, Config) -> basic(Conf) when is_list(Conf) -> - ?line 2 = + 2 = try my_div(4, 2) catch Class:Reason -> {Class,Reason} end, - ?line error = + error = try my_div(1, 0) catch error:badarith -> error end, - ?line error = + error = try 1.0 / zero() catch error:badarith -> error end, - ?line ok = + ok = try my_add(53, atom) catch error:badarith -> ok end, - ?line exit_nisse = + exit_nisse = try exit(nisse) catch exit:nisse -> exit_nisse end, - ?line ok = + ok = try throw(kalle) catch kalle -> ok @@ -94,27 +94,27 @@ basic(Conf) when is_list(Conf) -> %% Try some stuff where the compiler will optimize away the try. V = id({a,variable}), - ?line V = try V catch nisse -> error end, - ?line 42 = try 42 catch nisse -> error end, - ?line [V] = try [V] catch nisse -> error end, - ?line {ok,V} = try {ok,V} catch nisse -> error end, + V = try V catch nisse -> error end, + 42 = try 42 catch nisse -> error end, + [V] = try [V] catch nisse -> error end, + {ok,V} = try {ok,V} catch nisse -> error end, %% Same idea, but use an after too. - ?line V = try V catch nisse -> error after after_call() end, - ?line after_clean(), - ?line 42 = try 42 after after_call() end, - ?line after_clean(), - ?line [V] = try [V] catch nisse -> error after after_call() end, - ?line after_clean(), - ?line {ok,V} = try {ok,V} after after_call() end, + V = try V catch nisse -> error after after_call() end, + after_clean(), + 42 = try 42 after after_call() end, + after_clean(), + [V] = try [V] catch nisse -> error after after_call() end, + after_clean(), + {ok,V} = try {ok,V} after after_call() end, %% Try/of - ?line ok = try V of - {a,variable} -> ok - catch nisse -> erro - end, - + ok = try V of + {a,variable} -> ok + catch nisse -> erro + end, + ok. after_call() -> @@ -125,24 +125,24 @@ after_clean() -> lean_throw(Conf) when is_list(Conf) -> - ?line {throw,kalle} = + {throw,kalle} = try throw(kalle) catch Kalle -> {throw,Kalle} end, - ?line {exit,kalle} = + {exit,kalle} = try exit(kalle) catch Throw1 -> {throw,Throw1}; exit:Reason1 -> {exit,Reason1} end, - ?line {exit,kalle} = + {exit,kalle} = try exit(kalle) catch exit:Reason2 -> {exit,Reason2}; Throw2 -> {throw,Throw2} end, - ?line {exit,kalle} = + {exit,kalle} = try try exit(kalle) catch Throw3 -> {throw,Throw3} @@ -155,25 +155,25 @@ lean_throw(Conf) when is_list(Conf) -> try_of(Conf) when is_list(Conf) -> - ?line {ok,{some,content}} = + {ok,{some,content}} = try_of_1({value,{good,{some,content}}}), - ?line {error,[other,content]} = + {error,[other,content]} = try_of_1({value,{bad,[other,content]}}), - ?line {caught,{exit,{ex,it,[reason]}}} = + {caught,{exit,{ex,it,[reason]}}} = try_of_1({exit,{ex,it,[reason]}}), - ?line {caught,{throw,[term,{in,a,{tuple}}]}} = + {caught,{throw,[term,{in,a,{tuple}}]}} = try_of_1({throw,[term,{in,a,{tuple}}]}), - ?line {caught,{error,[bad,arg]}} = + {caught,{error,[bad,arg]}} = try_of_1({error,[bad,arg]}), - ?line {caught,{error,badarith}} = + {caught,{error,badarith}} = try_of_1({'div',{1,0}}), - ?line {caught,{error,badarith}} = + {caught,{error,badarith}} = try_of_1({'add',{a,0}}), - ?line {caught,{error,badarg}} = + {caught,{error,badarg}} = try_of_1({'abs',x}), - ?line {caught,{error,function_clause}} = + {caught,{error,function_clause}} = try_of_1(illegal), - ?line {error,{try_clause,{some,other_garbage}}} = + {error,{try_clause,{some,other_garbage}}} = try try_of_1({value,{some,other_garbage}}) catch error:Reason -> {error,Reason} end, @@ -191,29 +191,29 @@ try_of_1(X) -> try_after(Conf) when is_list(Conf) -> - ?line {{ok,[some,value],undefined},finalized} = + {{ok,[some,value],undefined},finalized} = try_after_1({value,{ok,[some,value]}},finalized), - ?line {{error,badarith,undefined},finalized} = + {{error,badarith,undefined},finalized} = try_after_1({'div',{1,0}},finalized), - ?line {{error,badarith,undefined},finalized} = + {{error,badarith,undefined},finalized} = try_after_1({'add',{1,a}},finalized), - ?line {{error,badarg,undefined},finalized} = + {{error,badarg,undefined},finalized} = try_after_1({'abs',a},finalized), - ?line {{error,[the,{reason}],undefined},finalized} = + {{error,[the,{reason}],undefined},finalized} = try_after_1({error,[the,{reason}]},finalized), - ?line {{throw,{thrown,[reason]},undefined},finalized} = + {{throw,{thrown,[reason]},undefined},finalized} = try_after_1({throw,{thrown,[reason]}},finalized), - ?line {{exit,{exited,{reason}},undefined},finalized} = + {{exit,{exited,{reason}},undefined},finalized} = try_after_1({exit,{exited,{reason}}},finalized), - ?line {{error,function_clause,undefined},finalized} = + {{error,function_clause,undefined},finalized} = try_after_1(function_clause,finalized), - ?line ok = + ok = try try_after_1({'add',{1,1}}, finalized) catch error:{try_clause,2} -> ok end, - ?line finalized = erase(try_after), - ?line ok = + finalized = erase(try_after), + ok = try try foo({exit,[reaso,{n}]}) after put(try_after, finalized) end @@ -242,7 +242,7 @@ try_after_1(X, Y) -> after_bind(Conf) when is_list(Conf) -> V = [make_ref(),self()|value], - ?line {value,{value,V}} = + {value,{value,V}} = after_bind_1({value,V}, V, {value,V}), ok. @@ -269,12 +269,12 @@ after_bind_1(X, V, Y) -> catch_oops(Conf) when is_list(Conf) -> V = {v,[a,l|u],{e},self()}, - ?line {value,V} = catch_oops_1({value,V}), - ?line {value,1} = catch_oops_1({'div',{1,1}}), - ?line {error,badarith} = catch_oops_1({'div',{1,0}}), - ?line {error,function_clause} = catch_oops_1(function_clause), - ?line {throw,V} = catch_oops_1({throw,V}), - ?line {exit,V} = catch_oops_1({exit,V}), + {value,V} = catch_oops_1({value,V}), + {value,1} = catch_oops_1({'div',{1,1}}), + {error,badarith} = catch_oops_1({'div',{1,0}}), + {error,function_clause} = catch_oops_1(function_clause), + {throw,V} = catch_oops_1({throw,V}), + {exit,V} = catch_oops_1({exit,V}), ok. catch_oops_1(X) -> @@ -293,10 +293,10 @@ catch_oops_1(X) -> after_oops(Conf) when is_list(Conf) -> V = {self(),make_ref()}, - ?line {{value,V},V} = after_oops_1({value,V}, {value,V}), - ?line {{exit,V},V} = after_oops_1({exit,V}, {value,V}), - ?line {{error,V},undefined} = after_oops_1({value,V}, {error,V}), - ?line {{error,function_clause},undefined} = + {{value,V},V} = after_oops_1({value,V}, {value,V}), + {{exit,V},V} = after_oops_1({exit,V}, {value,V}), + {{error,V},undefined} = after_oops_1({value,V}, {error,V}), + {{error,function_clause},undefined} = after_oops_1({exit,V}, function_clause), ok. @@ -317,39 +317,39 @@ after_oops_1(X, Y) -> eclectic(Conf) when is_list(Conf) -> V = {make_ref(),3.1415926535,[[]|{}]}, - ?line {{value,{value,V},V},V} = + {{value,{value,V},V},V} = eclectic_1({foo,{value,{value,V}}}, undefined, {value,V}), - ?line {{'EXIT',{V,[{?MODULE,foo,1,_}|_]}},V} = + {{'EXIT',{V,[{?MODULE,foo,1,_}|_]}},V} = eclectic_1({catch_foo,{error,V}}, undefined, {value,V}), - ?line {{error,{exit,V},{'EXIT',V}},V} = + {{error,{exit,V},{'EXIT',V}},V} = eclectic_1({foo,{error,{exit,V}}}, error, {value,V}), - ?line {{value,{value,V},V}, + {{value,{value,V},V}, {'EXIT',{badarith,[{?MODULE,my_add,2,_}|_]}}} = eclectic_1({foo,{value,{value,V}}}, undefined, {'add',{0,a}}), - ?line {{'EXIT',V},V} = + {{'EXIT',V},V} = eclectic_1({catch_foo,{exit,V}}, undefined, {throw,V}), - ?line {{error,{'div',{1,0}},{'EXIT',{badarith,[{?MODULE,my_div,2,_}|_]}}}, + {{error,{'div',{1,0}},{'EXIT',{badarith,[{?MODULE,my_div,2,_}|_]}}}, {'EXIT',V}} = eclectic_1({foo,{error,{'div',{1,0}}}}, error, {exit,V}), - ?line {{{error,V},{'EXIT',{V,[{?MODULE,foo,1,_}|_]}}}, + {{{error,V},{'EXIT',{V,[{?MODULE,foo,1,_}|_]}}}, {'EXIT',V}} = eclectic_1({catch_foo,{throw,{error,V}}}, undefined, {exit,V}), %% - ?line {{value,{value,{value,V},V}},V} = + {{value,{value,{value,V},V}},V} = eclectic_2({value,{value,V}}, undefined, {value,V}), - ?line {{value,{throw,{value,V},V}},V} = + {{value,{throw,{value,V},V}},V} = eclectic_2({throw,{value,V}}, throw, {value,V}), - ?line {{caught,{'EXIT',V}},undefined} = + {{caught,{'EXIT',V}},undefined} = eclectic_2({value,{value,V}}, undefined, {exit,V}), - ?line {{caught,{'EXIT',{V,[{?MODULE,foo,1,_}|_]}}},undefined} = + {{caught,{'EXIT',{V,[{?MODULE,foo,1,_}|_]}}},undefined} = eclectic_2({error,{value,V}}, throw, {error,V}), - ?line {{caught,{'EXIT',{badarg,[{erlang,abs,[V],_}|_]}}},V} = + {{caught,{'EXIT',{badarg,[{erlang,abs,[V],_}|_]}}},V} = eclectic_2({value,{'abs',V}}, undefined, {value,V}), - ?line {{caught,{'EXIT',{badarith,[{?MODULE,my_add,2,_}|_]}}},V} = + {{caught,{'EXIT',{badarith,[{?MODULE,my_add,2,_}|_]}}},V} = eclectic_2({exit,{'add',{0,a}}}, exit, {value,V}), - ?line {{caught,{'EXIT',V}},undefined} = + {{caught,{'EXIT',V}},undefined} = eclectic_2({value,{error,V}}, undefined, {exit,V}), - ?line {{caught,{'EXIT',{V,[{?MODULE,foo,1,_}|_]}}},undefined} = + {{caught,{'EXIT',{V,[{?MODULE,foo,1,_}|_]}}},undefined} = eclectic_2({throw,{'div',{1,0}}}, throw, {error,V}), ok. @@ -377,44 +377,44 @@ eclectic_2(X, C, Y) -> Catch = case catch - {Done, - try foo(X) of - V -> {value,V,foo(V)} - catch - C:D -> {C,D,foo(D)} - after - put(eclectic, foo(Y)) - end} of - {Done,Z} -> {value,Z}; - Z -> {caught,Z} - end, + {Done, + try foo(X) of + V -> {value,V,foo(V)} + catch + C:D -> {C,D,foo(D)} + after + put(eclectic, foo(Y)) + end} of + {Done,Z} -> {value,Z}; + Z -> {caught,Z} + end, {Catch,erase(eclectic)}. rethrow(Conf) when is_list(Conf) -> V = {a,[b,{c,self()},make_ref]}, - ?line {value2,value1} = + {value2,value1} = rethrow_1({value,V}, V), - ?line {caught2,{error,V}} = + {caught2,{error,V}} = rethrow_2({error,V}, undefined), - ?line {caught2,{exit,V}} = + {caught2,{exit,V}} = rethrow_1({exit,V}, error), - ?line {caught2,{throw,V}} = + {caught2,{throw,V}} = rethrow_1({throw,V}, undefined), - ?line {caught2,{throw,V}} = + {caught2,{throw,V}} = rethrow_2({throw,V}, undefined), - ?line {caught2,{error,badarith}} = + {caught2,{error,badarith}} = rethrow_1({'add',{0,a}}, throw), - ?line {caught2,{error,function_clause}} = + {caught2,{error,function_clause}} = rethrow_2(function_clause, undefined), - ?line {caught2,{error,{try_clause,V}}} = + {caught2,{error,{try_clause,V}}} = rethrow_1({value,V}, exit), - ?line {value2,{caught1,V}} = + {value2,{caught1,V}} = rethrow_1({error,V}, error), - ?line {value2,{caught1,V}} = + {value2,{caught1,V}} = rethrow_1({exit,V}, exit), - ?line {value2,caught1} = + {value2,caught1} = rethrow_2({throw,V}, V), ok. @@ -444,91 +444,91 @@ rethrow_2(X, C1) -> nested_of(Conf) when is_list(Conf) -> V = {[self()|make_ref()],1.4142136}, - ?line {{value,{value1,{V,x2}}}, - {V,x3}, - {V,x4}, - finalized} = + {{value,{value1,{V,x2}}}, + {V,x3}, + {V,x4}, + finalized} = nested_of_1({{value,{V,x1}},void,{V,x1}}, {value,{V,x2}}, {value,{V,x3}}, {value,{V,x4}}), - ?line {{caught,{throw,{V,x2}}}, - {V,x3}, - {V,x4}, - finalized} = + {{caught,{throw,{V,x2}}}, + {V,x3}, + {V,x4}, + finalized} = nested_of_1({{value,{V,x1}},void,{V,x1}}, {throw,{V,x2}}, {value,{V,x3}}, {value,{V,x4}}), - ?line {{caught,{error,badarith}}, - undefined, - {V,x4}, - finalized} = + {{caught,{error,badarith}}, + undefined, + {V,x4}, + finalized} = nested_of_1({{value,{V,x1}},void,{V,x1}}, {throw,{V,x2}}, {'div',{1,0}}, {value,{V,x4}}), - ?line {{caught,{error,badarith}}, - undefined, - undefined, - finalized} = + {{caught,{error,badarith}}, + undefined, + undefined, + finalized} = nested_of_1({{value,{V,x1}},void,{V,x1}}, {throw,{V,x2}}, {'div',{1,0}}, {'add',{0,b}}), %% - ?line {{caught,{error,{try_clause,{V,x1}}}}, - {V,x3}, - {V,x4}, - finalized} = + {{caught,{error,{try_clause,{V,x1}}}}, + {V,x3}, + {V,x4}, + finalized} = nested_of_1({{value,{V,x1}},void,try_clause}, void, {value,{V,x3}}, {value,{V,x4}}), - ?line {{caught,{exit,{V,x3}}}, - undefined, - {V,x4}, - finalized} = + {{caught,{exit,{V,x3}}}, + undefined, + {V,x4}, + finalized} = nested_of_1({{value,{V,x1}},void,try_clause}, void, {exit,{V,x3}}, {value,{V,x4}}), - ?line {{caught,{throw,{V,x4}}}, - undefined, - undefined, - finalized} = + {{caught,{throw,{V,x4}}}, + undefined, + undefined, + finalized} = nested_of_1({{value,{V,x1}},void,try_clause}, void, {exit,{V,x3}}, {throw,{V,x4}}), %% - ?line {{value,{caught1,{V,x2}}}, - {V,x3}, - {V,x4}, - finalized} = + {{value,{caught1,{V,x2}}}, + {V,x3}, + {V,x4}, + finalized} = nested_of_1({{error,{V,x1}},error,{V,x1}}, {value,{V,x2}}, {value,{V,x3}}, {value,{V,x4}}), - ?line {{caught,{error,badarith}}, - {V,x3}, - {V,x4}, - finalized} = + {{caught,{error,badarith}}, + {V,x3}, + {V,x4}, + finalized} = nested_of_1({{error,{V,x1}},error,{V,x1}}, {'add',{1,c}}, {value,{V,x3}}, {value,{V,x4}}), - ?line {{caught,{error,badarith}}, - undefined, - {V,x4}, - finalized} = + {{caught,{error,badarith}}, + undefined, + {V,x4}, + finalized} = nested_of_1({{error,{V,x1}},error,{V,x1}}, {'add',{1,c}}, {'div',{17,0}}, {value,{V,x4}}), - ?line {{caught,{error,badarg}}, - undefined, - undefined, - finalized} = + {{caught,{error,badarg}}, + undefined, + undefined, + finalized} = nested_of_1({{error,{V,x1}},error,{V,x1}}, {'add',{1,c}}, {'div',{17,0}}, {'abs',V}), %% - ?line {{caught,{error,badarith}}, - {V,x3}, - {V,x4}, - finalized} = + {{caught,{error,badarith}}, + {V,x3}, + {V,x4}, + finalized} = nested_of_1({{'add',{2,c}},rethrow,void}, void, {value,{V,x3}}, {value,{V,x4}}), - ?line {{caught,{error,badarg}}, - undefined, - {V,x4}, - finalized} = + {{caught,{error,badarg}}, + undefined, + {V,x4}, + finalized} = nested_of_1({{'add',{2,c}},rethrow,void}, void, {'abs',V}, {value,{V,x4}}), - ?line {{caught,{error,function_clause}}, - undefined, - undefined, - finalized} = + {{caught,{error,function_clause}}, + undefined, + undefined, + finalized} = nested_of_1({{'add',{2,c}},rethrow,void}, void, {'abs',V}, function_clause), ok. @@ -569,93 +569,93 @@ nested_of_1({X1,C1,V1}, nested_catch(Conf) when is_list(Conf) -> V = {[make_ref(),1.4142136,self()]}, - ?line {{value,{value1,{V,x2}}}, - {V,x3}, - {V,x4}, - finalized} = + {{value,{value1,{V,x2}}}, + {V,x3}, + {V,x4}, + finalized} = nested_catch_1({{value,{V,x1}},void,{V,x1}}, - {value,{V,x2}}, {value,{V,x3}}, {value,{V,x4}}), - ?line {{caught,{throw,{V,x2}}}, - {V,x3}, - {V,x4}, - finalized} = + {value,{V,x2}}, {value,{V,x3}}, {value,{V,x4}}), + {{caught,{throw,{V,x2}}}, + {V,x3}, + {V,x4}, + finalized} = nested_catch_1({{value,{V,x1}},void,{V,x1}}, - {throw,{V,x2}}, {value,{V,x3}}, {value,{V,x4}}), - ?line {{caught,{error,badarith}}, - undefined, - {V,x4}, - finalized} = + {throw,{V,x2}}, {value,{V,x3}}, {value,{V,x4}}), + {{caught,{error,badarith}}, + undefined, + {V,x4}, + finalized} = nested_catch_1({{value,{V,x1}},void,{V,x1}}, - {throw,{V,x2}}, {'div',{1,0}}, {value,{V,x4}}), - ?line {{caught,{error,badarith}}, - undefined, - undefined, - finalized} = + {throw,{V,x2}}, {'div',{1,0}}, {value,{V,x4}}), + {{caught,{error,badarith}}, + undefined, + undefined, + finalized} = nested_catch_1({{value,{V,x1}},void,{V,x1}}, - {throw,{V,x2}}, {'div',{1,0}}, {'add',{0,b}}), + {throw,{V,x2}}, {'div',{1,0}}, {'add',{0,b}}), %% - ?line {{caught,{error,{try_clause,{V,x1}}}}, - {V,x3}, - {V,x4}, - finalized} = + {{caught,{error,{try_clause,{V,x1}}}}, + {V,x3}, + {V,x4}, + finalized} = nested_catch_1({{value,{V,x1}},void,try_clause}, - void, {value,{V,x3}}, {value,{V,x4}}), - ?line {{caught,{exit,{V,x3}}}, - undefined, - {V,x4}, - finalized} = + void, {value,{V,x3}}, {value,{V,x4}}), + {{caught,{exit,{V,x3}}}, + undefined, + {V,x4}, + finalized} = nested_catch_1({{value,{V,x1}},void,try_clause}, - void, {exit,{V,x3}}, {value,{V,x4}}), - ?line {{caught,{throw,{V,x4}}}, - undefined, - undefined, - finalized} = + void, {exit,{V,x3}}, {value,{V,x4}}), + {{caught,{throw,{V,x4}}}, + undefined, + undefined, + finalized} = nested_catch_1({{value,{V,x1}},void,try_clause}, - void, {exit,{V,x3}}, {throw,{V,x4}}), + void, {exit,{V,x3}}, {throw,{V,x4}}), %% - ?line {{value,{caught1,{V,x2}}}, - {V,x3}, - {V,x4}, - finalized} = + {{value,{caught1,{V,x2}}}, + {V,x3}, + {V,x4}, + finalized} = nested_catch_1({{error,{V,x1}},error,{V,x1}}, - {value,{V,x2}}, {value,{V,x3}}, {value,{V,x4}}), - ?line {{caught,{error,badarith}}, - {V,x3}, - {V,x4}, - finalized} = + {value,{V,x2}}, {value,{V,x3}}, {value,{V,x4}}), + {{caught,{error,badarith}}, + {V,x3}, + {V,x4}, + finalized} = nested_catch_1({{error,{V,x1}},error,{V,x1}}, - {'add',{1,c}}, {value,{V,x3}}, {value,{V,x4}}), - ?line {{caught,{error,badarith}}, - undefined, - {V,x4}, - finalized} = + {'add',{1,c}}, {value,{V,x3}}, {value,{V,x4}}), + {{caught,{error,badarith}}, + undefined, + {V,x4}, + finalized} = nested_catch_1({{error,{V,x1}},error,{V,x1}}, - {'add',{1,c}}, {'div',{17,0}}, {value,{V,x4}}), - ?line {{caught,{error,badarg}}, - undefined, - undefined, - finalized} = + {'add',{1,c}}, {'div',{17,0}}, {value,{V,x4}}), + {{caught,{error,badarg}}, + undefined, + undefined, + finalized} = nested_catch_1({{error,{V,x1}},error,{V,x1}}, - {'add',{1,c}}, {'div',{17,0}}, {'abs',V}), + {'add',{1,c}}, {'div',{17,0}}, {'abs',V}), %% - ?line {{caught,{error,badarith}}, - {V,x3}, - {V,x4}, - finalized} = + {{caught,{error,badarith}}, + {V,x3}, + {V,x4}, + finalized} = nested_catch_1({{'add',{2,c}},rethrow,void}, - void, {value,{V,x3}}, {value,{V,x4}}), - ?line {{caught,{error,badarg}}, - undefined, - {V,x4}, - finalized} = + void, {value,{V,x3}}, {value,{V,x4}}), + {{caught,{error,badarg}}, + undefined, + {V,x4}, + finalized} = nested_catch_1({{'add',{2,c}},rethrow,void}, - void, {'abs',V}, {value,{V,x4}}), - ?line {{caught,{error,function_clause}}, - undefined, - undefined, - finalized} = + void, {'abs',V}, {value,{V,x4}}), + {{caught,{error,function_clause}}, + undefined, + undefined, + finalized} = nested_catch_1({{'add',{2,c}},rethrow,void}, - void, {'abs',V}, function_clause), + void, {'abs',V}, function_clause), ok. nested_catch_1({X1,C1,V1}, @@ -694,64 +694,64 @@ nested_catch_1({X1,C1,V1}, nested_after(Conf) when is_list(Conf) -> V = [{make_ref(),1.4142136,self()}], - ?line {value, + {value, {V,x3}, {value1,{V,x2}}, finalized} = nested_after_1({{value,{V,x1}},void,{V,x1}}, {value,{V,x2}}, {value,{V,x3}}), - ?line {{caught,{error,{V,x2}}}, + {{caught,{error,{V,x2}}}, {V,x3}, undefined, finalized} = nested_after_1({{value,{V,x1}},void,{V,x1}}, {error,{V,x2}}, {value,{V,x3}}), - ?line {{caught,{exit,{V,x3}}}, + {{caught,{exit,{V,x3}}}, undefined, undefined, finalized} = nested_after_1({{value,{V,x1}},void,{V,x1}}, {error,{V,x2}}, {exit,{V,x3}}), %% - ?line {{caught,{error,{try_clause,{V,x1}}}}, + {{caught,{error,{try_clause,{V,x1}}}}, {V,x3}, undefined, finalized} = nested_after_1({{value,{V,x1}},void,try_clause}, void, {value,{V,x3}}), - ?line {{caught,{error,badarith}}, + {{caught,{error,badarith}}, undefined, undefined, finalized} = nested_after_1({{value,{V,x1}},void,try_clause}, void, {'div',{17,0}}), %% - ?line {value, + {value, {V,x3}, {caught1,{V,x2}}, finalized} = nested_after_1({{throw,{V,x1}},throw,{V,x1}}, {value,{V,x2}}, {value,{V,x3}}), - ?line {{caught,{error,badarith}}, + {{caught,{error,badarith}}, {V,x3}, undefined, finalized} = nested_after_1({{throw,{V,x1}},throw,{V,x1}}, {'add',{a,b}}, {value,{V,x3}}), - ?line {{caught,{error,badarg}}, + {{caught,{error,badarg}}, undefined, undefined, finalized} = nested_after_1({{throw,{V,x1}},throw,{V,x1}}, {'add',{a,b}}, {'abs',V}), %% - ?line {{caught,{throw,{V,x1}}}, + {{caught,{throw,{V,x1}}}, {V,x3}, undefined, finalized} = nested_after_1({{throw,{V,x1}},rethrow,void}, void, {value,{V,x3}}), - ?line {{caught,{error,badarith}}, + {{caught,{error,badarith}}, undefined, undefined, finalized} = @@ -843,12 +843,12 @@ my_abs(X) -> abs(X). last_call_optimization(Config) when is_list(Config) -> - ?line error = in_tail(dum), - ?line StkSize0 = in_tail(0), - ?line StkSize = in_tail(50000), + error = in_tail(dum), + StkSize0 = in_tail(0), + StkSize = in_tail(50000), io:format("StkSize0 = ~p", [StkSize0]), io:format("StkSize = ~p", [StkSize]), - ?line StkSize = StkSize0, + StkSize = StkSize0, ok. in_tail(E) -> @@ -891,20 +891,20 @@ do_bool(A0, B) -> plain_catch_coverage(Config) when is_list(Config) -> %% Cover some code in beam_block:alloc_may_pass/1. - ?line {a,[42]} = do_plain_catch_list(42). + {a,[42]} = do_plain_catch_list(42). do_plain_catch_list(X) -> B = [X], catch id({a,B}). andalso_orelse(Config) when is_list(Config) -> - ?line {2,{a,42}} = andalso_orelse_1(true, {a,42}), - ?line {b,{b}} = andalso_orelse_1(false, {b}), - ?line {catched,no_tuple} = andalso_orelse_1(false, no_tuple), + {2,{a,42}} = andalso_orelse_1(true, {a,42}), + {b,{b}} = andalso_orelse_1(false, {b}), + {catched,no_tuple} = andalso_orelse_1(false, no_tuple), - ?line ok = andalso_orelse_2({type,[a]}), - ?line also_ok = andalso_orelse_2({type,[]}), - ?line also_ok = andalso_orelse_2({type,{a}}), + ok = andalso_orelse_2({type,[a]}), + also_ok = andalso_orelse_2({type,[]}), + also_ok = andalso_orelse_2({type,{a}}), ok. andalso_orelse_1(A, B) -> diff --git a/lib/compiler/test/warnings_SUITE.erl b/lib/compiler/test/warnings_SUITE.erl index a964afe5a1..d66f2d5053 100644 --- a/lib/compiler/test/warnings_SUITE.erl +++ b/lib/compiler/test/warnings_SUITE.erl @@ -27,9 +27,9 @@ -define(privdir, "warnings_SUITE_priv"). -define(t, test_server). -else. --include_lib("test_server/include/test_server.hrl"). --define(datadir, ?config(data_dir, Conf)). --define(privdir, ?config(priv_dir, Conf)). +-include_lib("common_test/include/ct.hrl"). +-define(datadir, proplists:get_value(data_dir, Conf)). +-define(privdir, proplists:get_value(priv_dir, Conf)). -endif. -export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, @@ -41,21 +41,18 @@ files/1,effect/1,bin_opt_info/1,bin_construction/1, comprehensions/1,maps/1,maps_bin_opt_info/1, redundant_boolean_clauses/1, - latin1_fallback/1,underscore/1,no_warnings/1]). - -% Default timetrap timeout (set in init_per_testcase). --define(default_timeout, ?t:minutes(2)). + latin1_fallback/1,underscore/1,no_warnings/1, + bit_syntax/1]). init_per_testcase(_Case, Config) -> - ?line Dog = ?t:timetrap(?default_timeout), - [{watchdog, Dog} | Config]. + Config. -end_per_testcase(_Case, Config) -> - Dog = ?config(watchdog, Config), - test_server:timetrap_cancel(Dog), +end_per_testcase(_Case, _Config) -> ok. -suite() -> [{ct_hooks,[ts_install_cth]}]. +suite() -> + [{ct_hooks,[ts_install_cth]}, + {timetrap,{minutes,2}}]. all() -> test_lib:recompile(?MODULE), @@ -68,7 +65,7 @@ groups() -> bin_opt_info,bin_construction,comprehensions,maps, maps_bin_opt_info, redundant_boolean_clauses,latin1_fallback, - underscore,no_warnings]}]. + underscore,no_warnings,bit_syntax]}]. init_per_suite(Config) -> Config. @@ -103,7 +100,7 @@ pattern(Config) when is_list(Config) -> [{2,v3_core,nomatch}, {6,v3_core,nomatch}, {11,v3_core,nomatch} ] }}], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), ok. pattern2(Config) when is_list(Config) -> @@ -127,7 +124,7 @@ pattern2(Config) when is_list(Config) -> {4,sys_core_fold,no_clause_match}, {5,sys_core_fold,nomatch_clause_type}, {6,sys_core_fold,nomatch_clause_type}]}}], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), %% Disable Core Erlang optimizations. v3_kernel should produce %% a warning for the clause that didn't match. @@ -136,7 +133,7 @@ pattern2(Config) when is_list(Config) -> [nowarn_unused_vars,no_copt], {warnings, [{2,v3_kernel,{nomatch_shadow,1}}]}}], - ?line [] = run(Config, Ts2), + [] = run(Config, Ts2), ok. pattern3(Config) when is_list(Config) -> @@ -152,7 +149,7 @@ pattern3(Config) when is_list(Config) -> [nowarn_unused_vars], {warnings, [{4,v3_kernel,{nomatch_shadow,2}}]}}], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), ok. @@ -213,7 +210,7 @@ pattern4(Config) when is_list(Config) -> {23,sys_core_fold,no_clause_match}, {33,sys_core_fold,no_clause_match} ]}}], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), ok. @@ -256,7 +253,7 @@ guard(Config) when is_list(Config) -> {11,sys_core_fold,nomatch_guard}, {11,sys_core_fold,{eval_failure,badarg}} ]}}], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), ok. @@ -321,7 +318,7 @@ bool_cases(Config) when is_list(Config) -> [{6,sys_core_fold,nomatch_shadow}, {13,sys_core_fold,nomatch_shadow}, {18,sys_core_fold,nomatch_clause_type} ]} }], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), ok. bad_apply(Config) when is_list(Config) -> @@ -340,11 +337,11 @@ bad_apply(Config) when is_list(Config) -> {4,v3_kernel,bad_call}, {5,v3_kernel,bad_call}, {6,v3_kernel,bad_call}]}}], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), %% Also verify that the generated code generates the correct error. - ?line try erlang:42() of - _ -> ?line ?t:fail() + try erlang:42() of + _ -> ct:fail(should_fail) catch error:badarg -> ok end, @@ -368,7 +365,7 @@ files(Config) when is_list(Config) -> [{"file1",[{17,sys_core_fold,{eval_failure,badarith}}]}, {"file2",[{10,sys_core_fold,{eval_failure,badarith}}]}]}}], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), ok. %% Test warnings for term construction and BIF calls in effect context. @@ -514,7 +511,7 @@ effect(Config) when is_list(Config) -> {28,sys_core_fold,useless_building}, {36,sys_core_fold,{no_effect,{erlang,'=:=',2}}}, {38,sys_core_fold,{no_effect,{erlang,get_cookie,0}}}]}}], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), ok. bin_opt_info(Config) when is_list(Config) -> @@ -537,14 +534,14 @@ bin_opt_info(Config) when is_list(Config) -> {5,beam_bsm,{no_bin_opt,{{t1,1},no_suitable_bs_start_match}}}, {9,beam_bsm,{no_bin_opt, {binary_used_in,{extfunc,erlang,split_binary,2}}}} ]}}], - ?line [] = run(Config, Ts1), + [] = run(Config, Ts1), %% For coverage: don't give the bin_opt_info option. Ts2 = [{bsm2, Code, [], []}], - ?line [] = run(Config, Ts2), + [] = run(Config, Ts2), ok. bin_construction(Config) when is_list(Config) -> @@ -561,7 +558,7 @@ bin_construction(Config) when is_list(Config) -> [], {warnings,[{4,sys_core_fold,embedded_binary_size}, {8,sys_core_fold,{embedded_unit,8,28}}]}}], - ?line [] = run(Config, Ts), + [] = run(Config, Ts), ok. @@ -783,6 +780,50 @@ no_warnings(Config) when is_list(Config) -> run(Config, Ts), ok. +bit_syntax(Config) -> + Ts = [{?FUNCTION_NAME, + <<"a(<<-1>>) -> ok; + a(<<1023>>) -> ok; + a(<<777/signed>>) -> ok; + a(<<a/binary>>) -> ok; + a(<<a/integer>>) -> ok; + a(<<a/float>>) -> ok; + a(<<a/utf8>>) -> ok; + a(<<a/utf16>>) -> ok; + a(<<a/utf32>>) -> ok; + a(<<a/utf32>>) -> ok. + b(Bin) -> Sz = bad, <<42:Sz>> = Bin. + c(Sz, Bin) -> + case Bin of + <<-42:Sz/unsigned>> -> ok; + <<42:Sz/float>> -> ok; + <<42:Sz/binary>> -> ok + end. + ">>, + [], + {warnings,[{1,sys_core_fold,no_clause_match}, + {1,sys_core_fold,{nomatch_bit_syntax_unsigned,-1}}, + {2,sys_core_fold,{nomatch_bit_syntax_truncated, + unsigned,1023,8}}, + {3,sys_core_fold,{nomatch_bit_syntax_truncated, + signed,777,8}}, + {4,sys_core_fold,{nomatch_bit_syntax_type,a,binary}}, + {5,sys_core_fold,{nomatch_bit_syntax_type,a,integer}}, + {6,sys_core_fold,{nomatch_bit_syntax_type,a,float}}, + {7,sys_core_fold,{nomatch_bit_syntax_type,a,utf8}}, + {8,sys_core_fold,{nomatch_bit_syntax_type,a,utf16}}, + {9,sys_core_fold,{nomatch_bit_syntax_type,a,utf32}}, + {10,sys_core_fold,{nomatch_bit_syntax_type,a,utf32}}, + {11,sys_core_fold,no_clause_match}, + {11,sys_core_fold,{nomatch_bit_syntax_size,bad}}, + {14,sys_core_fold,{nomatch_bit_syntax_unsigned,-42}}, + {16,sys_core_fold,{nomatch_bit_syntax_type,42,binary}} + ]} + }], + run(Config, Ts), + ok. + + %%% %%% End of test cases. %%% @@ -793,7 +834,7 @@ run(Config, Tests) -> E -> BadL; Bad -> - ?t:format("~nTest ~p failed. Expected~n ~p~n" + io:format("~nTest ~p failed. Expected~n ~p~n" "but got~n ~p~n", [N, E, Bad]), fail() end @@ -806,33 +847,32 @@ run(Config, Tests) -> run_test(Conf, Test0, Warnings) -> Module = "warnings_"++test_lib:uniq(), Filename = Module ++ ".erl", - ?line DataDir = ?privdir, + DataDir = ?privdir, Test = ["-module(", Module, "). ", Test0], - ?line File = filename:join(DataDir, Filename), - ?line Opts = [binary,export_all,return|Warnings], - ?line ok = file:write_file(File, Test), + File = filename:join(DataDir, Filename), + Opts = [binary,export_all,return|Warnings], + ok = file:write_file(File, Test), %% Compile once just to print all warnings. - ?line compile:file(File, [binary,export_all,report|Warnings]), + compile:file(File, [binary,export_all,report|Warnings]), %% Test result of compilation. - ?line Res = case compile:file(File, Opts) of - {ok, _M, Bin, []} when is_binary(Bin) -> - []; - {ok, _M, Bin, Ws0} when is_binary(Bin) -> - %% We are not interested in warnings from - %% erl_lint here. - WsL = [{F,[W || {_,Mod,_}=W <- Ws, - Mod =/= erl_lint]} || - {F,Ws} <- Ws0], - case WsL of - [{_File,Ws}] -> {warnings, Ws}; - _ -> list_to_tuple([warnings, WsL]) - end - end, + Res = case compile:file(File, Opts) of + {ok, _M, Bin, []} when is_binary(Bin) -> + []; + {ok, _M, Bin, Ws0} when is_binary(Bin) -> + %% We are not interested in warnings from + %% erl_lint here. + WsL = [{F,[W || {_,Mod,_}=W <- Ws, + Mod =/= erl_lint]} || + {F,Ws} <- Ws0], + case WsL of + [{_File,Ws}] -> {warnings, Ws}; + _ -> list_to_tuple([warnings, WsL]) + end + end, file:delete(File), Res. fail() -> - io:format("failed~n"), - ?t:fail(). + ct:fail(failed). |