~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

Viewing changes to lib/hipe/icode/hipe_beam_to_icode.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-05-07 15:07:37 UTC
  • mfrom: (1.2.1 upstream) (5.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20090507150737-i4yb5elwinm7r0hc
Tags: 1:13.b-dfsg1-1
* Removed another bunch of non-free RFCs from original tarball
  (closes: #527053).
* Fixed build-dependencies list by adding missing comma. This requires
  libsctp-dev again. Also, added libsctp1 dependency to erlang-base and
  erlang-base-hipe packages because the shared library is loaded via
  dlopen now and cannot be added using dh_slibdeps (closes: #526682).
* Weakened dependency of erlang-webtool on erlang-observer to recommends
  to avoid circular dependencies (closes: #526627).
* Added solaris-i386 to HiPE enabled architectures.
* Made script sources in /usr/lib/erlang/erts-*/bin directory executable,
  which is more convenient if a user wants to create a target Erlang system.
* Shortened extended description line for erlang-dev package to make it
  fit 80x25 terminals.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%% -*- erlang-indent-level: 2 -*-
 
2
%%
 
3
%% %CopyrightBegin%
 
4
%% 
 
5
%% Copyright Ericsson AB 2001-2009. All Rights Reserved.
 
6
%% 
 
7
%% The contents of this file are subject to the Erlang Public License,
 
8
%% Version 1.1, (the "License"); you may not use this file except in
 
9
%% compliance with the License. You should have received a copy of the
 
10
%% Erlang Public License along with this software. If not, it can be
 
11
%% retrieved online at http://www.erlang.org/.
 
12
%% 
 
13
%% Software distributed under the License is distributed on an "AS IS"
 
14
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
15
%% the License for the specific language governing rights and limitations
 
16
%% under the License.
 
17
%% 
 
18
%% %CopyrightEnd%
 
19
%%
2
20
%%=======================================================================
3
21
%% File        : hipe_beam_to_icode.erl
4
22
%% Author      : Kostis Sagonas
68
86
 
69
87
-record(beam_const, {value :: simple_const()}). % defined in hipe_icode.hrl
70
88
 
71
 
-record(closure_info, {mfa :: mfa(), arity :: byte(), fv_arity :: byte()}).
 
89
-record(closure_info, {mfa :: mfa(), arity :: arity(), fv_arity :: arity()}).
72
90
 
73
91
-record(environment, {mfa :: mfa(), entry :: non_neg_integer()}).
74
92
 
85
103
 
86
104
module(BeamFuns, Options) ->
87
105
  BeamCode0 = [beam_disasm:function__code(F) || F <- BeamFuns],
88
 
  BeamCode1 = exclude_module_info_code(BeamCode0, []),
89
 
  {ModCode, ClosureInfo} = preprocess_code(BeamCode1),
 
106
  {ModCode, ClosureInfo} = preprocess_code(BeamCode0),
90
107
  pp_beam(ModCode, Options),
91
108
  [trans_beam_function_chunk(FunCode, ClosureInfo) || FunCode <- ModCode].
92
109
 
93
110
trans_beam_function_chunk(FunBeamCode, ClosureInfo) ->
94
 
  {M,F,A} = find_mfa(FunBeamCode),
 
111
  {M,F,A} = MFA = find_mfa(FunBeamCode),
95
112
  Icode = trans_mfa_code(M,F,A, FunBeamCode, ClosureInfo),
96
 
  {{M,F,A},Icode}.
97
 
 
98
 
%%-----------------------------------------------------------------------
99
 
%% The code chunks of module_info/[0,1] are excluded from the
100
 
%% compilation to native code, since they are just dummy stubs.
101
 
%% It is the BEAM loader that creates their real code, and HiPE relies
102
 
%% on it to generate proper code for module_info/[0,1].
103
 
%%-----------------------------------------------------------------------
104
 
 
105
 
exclude_module_info_code([FunCode|FunCodes], Acc) ->
106
 
  case FunCode of
107
 
    [{label,L},{label,_},{func_info,M,F,A}|Insns] ->
108
 
      NewFunCode = [{label,L},{func_info,M,F,A}|Insns],
109
 
      exclude_module_info_code([NewFunCode|FunCodes], Acc);
110
 
    [{label,_},{func_info,_,{atom,module_info},A}|_] when A =:= 0; A =:= 1->
111
 
      exclude_module_info_code(FunCodes, Acc);
112
 
    _Other ->
113
 
      exclude_module_info_code(FunCodes, [FunCode|Acc])
114
 
  end;
115
 
exclude_module_info_code([], Acc) ->
116
 
  lists:reverse(Acc).
 
113
  {MFA,Icode}.
117
114
 
118
115
%%-----------------------------------------------------------------------
119
116
%% @doc
129
126
 
130
127
-spec mfa(list(), mfa(), comp_options()) -> hipe_beam_to_icode_ret().
131
128
 
132
 
mfa(_, {M,module_info,A}, _) when is_atom(M), (A =:= 0 orelse A =:= 1) ->
133
 
  [];  % the module_info/[0,1] functions are just stubs in a BEAM file
134
129
mfa(BeamFuns, {M,F,A} = MFA, Options)
135
130
  when is_atom(M), is_atom(F), is_integer(A) ->
136
131
  BeamCode0 = [beam_disasm:function__code(F) || F <- BeamFuns],
180
175
  Env1 = env__mk_env(M, F, A, hipe_icode:label_name(FunLbl)),
181
176
  Code1 = lists:flatten(trans_fun(FunBeamCode,Env1)),
182
177
  Code2 = fix_fallthroughs(fix_catches(Code1)),
 
178
  MFA = {M,F,A},
183
179
  %% Debug code
184
180
  ?IF_DEBUG_LEVEL(5,
185
 
                  {Code3,_Env3} = ?mk_debugcode({M,F,A}, Env2, Code2),
 
181
                  {Code3,_Env3} = ?mk_debugcode(MFA, Env2, Code2),
186
182
                  {Code3,_Env3} = {Code2,Env1}),
187
183
  %% For stack optimization
188
184
  Leafness = leafness(Code3),
193
189
       false -> Code3;
194
190
       true -> [mk_redtest()|Code3]
195
191
     end],
196
 
  IsClosure = case get_closure_info({M,F,A}, ClosureInfo) of
197
 
                not_a_closure -> false;
198
 
                _ -> true
199
 
              end,
200
 
  Code5 = hipe_icode:mk_icode({M,F,A}, FunArgs, IsClosure, IsLeaf,
 
192
  IsClosure = get_closure_info(MFA, ClosureInfo) =/= not_a_closure,
 
193
  Code5 = hipe_icode:mk_icode(MFA, FunArgs, IsClosure, IsLeaf,
201
194
                              remove_dead_code(Code4),
202
195
                              hipe_gensym:var_range(icode),
203
196
                              hipe_gensym:label_range(icode)),
204
197
  Icode = %% If this function is the code for a closure ...
205
 
    case get_closure_info({M,F,A}, ClosureInfo) of
 
198
    case get_closure_info(MFA, ClosureInfo) of
206
199
      not_a_closure -> Code5;
207
200
      CI -> %% ... then patch the code to 
208
201
        %% get the free_vars from the closure
305
298
  Goto = hipe_icode:mk_goto(hipe_icode:label_name(EntryPt)),
306
299
  Mov = hipe_icode:mk_move(V, hipe_icode:mk_const(function_clause)),
307
300
  Fail = hipe_icode:mk_fail([V],error),
308
 
  [Goto,Begin,Mov,Fail,EntryPt | trans_fun(Instructions,Env)];
 
301
  [Goto, Begin, Mov, Fail, EntryPt | trans_fun(Instructions, Env)];
309
302
%%--- label ---
310
303
trans_fun([{label,L1},{label,L2}|Instructions], Env) ->
311
304
  %% Old BEAM code can have two consecutive labels.
317
310
  [mk_label(L) | trans_fun(Instructions, Env)];
318
311
%%--- int_code_end --- SHOULD NEVER OCCUR HERE
319
312
%%--- call ---
320
 
trans_fun([{call,_N,MFA={_M,_F,A}}|Instructions], Env) ->
 
313
trans_fun([{call,_N,{_M,_F,A}=MFA}|Instructions], Env) ->
321
314
  Args = extract_fun_args(A),
322
315
  Dst = [mk_var({r,0})],
323
 
  I = trans_call(MFA,Dst,Args,local),
324
 
  [I | trans_fun(Instructions,Env)];
 
316
  I = trans_call(MFA, Dst, Args, local),
 
317
  [I | trans_fun(Instructions, Env)];
325
318
%%--- call_last ---
326
319
%% Differs from call_only in that it deallocates the environment
327
 
trans_fun([{call_last,_N,MFA={M,F,A},_}|Instructions], Env) ->
 
320
trans_fun([{call_last,_N,{_M,_F,A}=MFA,_}|Instructions], Env) ->
328
321
  %% IS IT OK TO IGNORE LAST ARG ??
329
322
  ?no_debug_msg("  translating call_last: ~p ...~n", [Env]),
330
323
  case env__get_mfa(Env) of
331
 
    {M,F,A} ->
 
324
    MFA ->
332
325
      %% Does this case really happen, or is it covered by call_only?
333
326
      Entry = env__get_entry(Env),
334
327
      [hipe_icode:mk_comment('tail_recursive'), % needed by leafness/2
335
328
       hipe_icode:mk_goto(Entry) | trans_fun(Instructions,Env)];
336
329
    _ ->
337
330
      Args = extract_fun_args(A),
338
 
      I = trans_enter(MFA,Args,local),
339
 
      [I | trans_fun(Instructions,Env)]
 
331
      I = trans_enter(MFA, Args, local),
 
332
      [I | trans_fun(Instructions, Env)]
340
333
  end;
341
334
%%--- call_only ---
342
335
%% Used when the body contains only one call in which case 
343
336
%% an environment is not needed/created.
344
 
trans_fun([{call_only,_N,MFA={_M,_F,A}}|Instructions], Env) ->
 
337
trans_fun([{call_only,_N,{_M,_F,A}=MFA}|Instructions], Env) ->
345
338
  ?no_debug_msg("  translating call_only: ~p ...~n", [Env]),
346
339
  case env__get_mfa(Env) of
347
340
    MFA ->
432
425
  [Susp, Loop | trans_fun(Instructions,Env)];
433
426
%%--- wait_timeout ---
434
427
trans_fun([{wait_timeout,{_,Lbl},Reg}|Instructions], Env) ->
435
 
  {Movs,[Temp],Env1} = get_constants_in_temps([Reg],Env),
436
 
  SetTmout = hipe_icode:mk_primop([],set_timeout,[Temp]),
 
428
  {Movs,[_]=Temps,Env1} = get_constants_in_temps([Reg],Env),
 
429
  SetTmout = hipe_icode:mk_primop([],set_timeout,Temps),
437
430
  DoneLbl = mk_label(new),
438
431
  SuspTmout = hipe_icode:mk_if(suspend_msg_timeout,[],
439
432
                               map_label(Lbl),hipe_icode:label_name(DoneLbl)),
523
516
  {Code,Env1} = trans_type_test(cons,Lbl,Arg,Env),
524
517
  [Code | trans_fun(Instructions,Env1)];
525
518
%%--- is_tuple ---
526
 
trans_fun([{test,is_tuple,{f,Lbl},[Xreg]},
527
 
           {test,test_arity,{f,Lbl},[Xreg,_]=Args}|Instructions], Env) ->
528
 
  trans_fun([{test,test_arity,{f,Lbl},Args}|Instructions],Env);
 
519
trans_fun([{test,is_tuple,{f,_Lbl}=FLbl,[Xreg]},
 
520
           {test,test_arity,FLbl,[Xreg,_]=Args}|Instructions], Env) ->
 
521
  trans_fun([{test,test_arity,FLbl,Args}|Instructions],Env);
529
522
trans_fun([{test,is_tuple,{_,Lbl},[Arg]}|Instructions], Env) ->
530
523
  {Code,Env1} = trans_type_test(tuple,Lbl,Arg,Env),
531
524
  [Code | trans_fun(Instructions,Env1)];
565
558
  NewContLbl = mk_label(new),
566
559
  [{'catch',N,EndLabel},NewContLbl | trans_fun(Instructions,Env)];
567
560
%%--- catch_end --- ITS PROCESSING IS POSTPONED
568
 
trans_fun([{catch_end,N}|Instructions], Env) ->
569
 
  [{catch_end,N} | trans_fun(Instructions,Env)];
 
561
trans_fun([{catch_end,_N}=I|Instructions], Env) ->
 
562
  [I | trans_fun(Instructions,Env)];
570
563
%%--- try --- ITS PROCESSING IS POSTPONED
571
564
trans_fun([{'try',N,{_,EndLabel}}|Instructions], Env) ->
572
565
  NewContLbl = mk_label(new),
575
568
trans_fun([{try_end,_N}|Instructions], Env) ->
576
569
  [hipe_icode:mk_end_try() | trans_fun(Instructions,Env)];
577
570
%%--- try_case --- ITS PROCESSING IS POSTPONED
578
 
trans_fun([{try_case,N}|Instructions], Env) ->
579
 
  [{try_case,N} | trans_fun(Instructions,Env)];
 
571
trans_fun([{try_case,_N}=I|Instructions], Env) ->
 
572
  [I | trans_fun(Instructions,Env)];
580
573
%%--- try_case_end ---
581
574
trans_fun([{try_case_end,Arg}|Instructions], Env) ->
582
575
  BadArg = trans_arg(Arg),
583
576
  ErrVar = mk_var(new),
584
 
  V = mk_var(new),
 
577
  Vs = [mk_var(new)],
585
578
  Atom = hipe_icode:mk_move(ErrVar,hipe_icode:mk_const(try_clause)),
586
 
  Tuple = hipe_icode:mk_primop([V],mktuple,[ErrVar,BadArg]),
587
 
  Fail = hipe_icode:mk_fail([V],error),
 
579
  Tuple = hipe_icode:mk_primop(Vs,mktuple,[ErrVar,BadArg]),
 
580
  Fail = hipe_icode:mk_fail(Vs,error),
588
581
  [Atom,Tuple,Fail | trans_fun(Instructions,Env)];
589
582
%%--- raise ---
590
583
trans_fun([{raise,{f,0},[Reg1,Reg2],{x,0}}|Instructions], Env) ->
594
587
  [Fail | trans_fun(Instructions,Env)];
595
588
%%--- get_list ---
596
589
trans_fun([{get_list,List,Head,Tail}|Instructions], Env) ->
597
 
  I1 = hipe_icode:mk_primop([mk_var(Head)],unsafe_hd,[trans_arg(List)]),
598
 
  I2 = hipe_icode:mk_primop([mk_var(Tail)],unsafe_tl,[trans_arg(List)]),
 
590
  TransList = [trans_arg(List)],
 
591
  I1 = hipe_icode:mk_primop([mk_var(Head)],unsafe_hd,TransList),
 
592
  I2 = hipe_icode:mk_primop([mk_var(Tail)],unsafe_tl,TransList),
599
593
  %% Handle the cases where the dest overwrites the src!!
600
594
  if 
601
 
    Head /= List ->
 
595
    Head =/= List ->
602
596
      [I1, I2 | trans_fun(Instructions,Env)];
603
 
    Tail /= List ->
 
597
    Tail =/= List ->
604
598
      [I2, I1 | trans_fun(Instructions,Env)];
605
599
    true ->
606
600
      %% XXX: We should take care of this case!!!!!
643
637
trans_fun([{badmatch,Arg}|Instructions], Env) ->
644
638
  BadVar = trans_arg(Arg),
645
639
  ErrVar = mk_var(new),
646
 
  V = mk_var(new),
 
640
  Vs = [mk_var(new)],
647
641
  Atom = hipe_icode:mk_move(ErrVar,hipe_icode:mk_const(badmatch)),
648
 
  Tuple = hipe_icode:mk_primop([V],mktuple,[ErrVar,BadVar]),
649
 
  Fail = hipe_icode:mk_fail([V],error),
 
642
  Tuple = hipe_icode:mk_primop(Vs,mktuple,[ErrVar,BadVar]),
 
643
  Fail = hipe_icode:mk_fail(Vs,error),
650
644
  [Atom,Tuple,Fail | trans_fun(Instructions,Env)];
651
645
%%--- if_end ---
652
646
trans_fun([if_end|Instructions], Env) ->
658
652
trans_fun([{case_end,Arg}|Instructions], Env) ->
659
653
  BadArg = trans_arg(Arg),
660
654
  ErrVar = mk_var(new),
661
 
  V = mk_var(new),
 
655
  Vs = [mk_var(new)],
662
656
  Atom = hipe_icode:mk_move(ErrVar,hipe_icode:mk_const(case_clause)),
663
 
  Tuple = hipe_icode:mk_primop([V],mktuple,[ErrVar,BadArg]),
664
 
  Fail = hipe_icode:mk_fail([V],error),
 
657
  Tuple = hipe_icode:mk_primop(Vs,mktuple,[ErrVar,BadArg]),
 
658
  Fail = hipe_icode:mk_fail(Vs,error),
665
659
  [Atom,Tuple,Fail | trans_fun(Instructions,Env)];
666
660
%%--- enter_fun ---
667
661
trans_fun([{call_fun,N},{deallocate,_},return|Instructions], Env) ->
811
805
  end;
812
806
trans_fun([{bs_context_to_binary,Var}|Instructions], Env) -> 
813
807
  %% the current match buffer
814
 
  IcodeVar = trans_arg(Var),
815
 
  [hipe_icode:mk_primop([IcodeVar],{hipe_bs_primop,bs_context_to_binary},[IcodeVar])|
 
808
  IVars = [trans_arg(Var)],
 
809
  [hipe_icode:mk_primop(IVars,{hipe_bs_primop,bs_context_to_binary},IVars)|
816
810
   trans_fun(Instructions, Env)];
817
811
trans_fun([{bs_append,{f,Lbl},Size,W,R,U,Binary,{field_flags,F},Dst}| 
818
812
           Instructions], Env) -> 
838
832
                 [IcodeDst,Base,Offset],
839
833
                 Base, Offset, Env, Instructions);
840
834
trans_fun([bs_init_writable|Instructions], Env) -> 
841
 
  Var = mk_var({x,0}), %{x,0} is implict arg and dst
842
 
  [hipe_icode:mk_primop([Var],{hipe_bs_primop,bs_init_writable},[Var]),
 
835
  Vars = [mk_var({x,0})], %{x,0} is implict arg and dst
 
836
  [hipe_icode:mk_primop(Vars,{hipe_bs_primop,bs_init_writable},Vars),
843
837
   trans_fun(Instructions, Env)];
844
 
trans_fun([{bs_save2,Ms,IndexName}| Instructions], Env) ->
 
838
trans_fun([{bs_save2,Ms,IndexName}|Instructions], Env) ->
845
839
  Index =
846
840
    case IndexName of
847
841
      {atom, start} -> 0;
848
842
      _ -> IndexName+1
849
843
    end,
850
 
  MsVar = mk_var(Ms),
851
 
  [hipe_icode:mk_primop([MsVar],{hipe_bs_primop,{bs_save,Index}},[MsVar]) |
 
844
  MsVars = [mk_var(Ms)],
 
845
  [hipe_icode:mk_primop(MsVars,{hipe_bs_primop,{bs_save,Index}},MsVars) |
852
846
   trans_fun(Instructions, Env)];
853
847
trans_fun([{bs_restore2,Ms,IndexName}|Instructions], Env) ->
854
848
  Index =
856
850
      {atom, start} -> 0;
857
851
      _ -> IndexName+1
858
852
    end,
859
 
  MsVar = mk_var(Ms),
860
 
  [hipe_icode:mk_primop([MsVar],{hipe_bs_primop,{bs_restore,Index}},[MsVar]) |
 
853
  MsVars = [mk_var(Ms)],
 
854
  [hipe_icode:mk_primop(MsVars,{hipe_bs_primop,{bs_restore,Index}},MsVars) |
861
855
   trans_fun(Instructions, Env)];
862
856
trans_fun([{test,bs_test_tail2,{f,Lbl},[Ms,Numbits]}| Instructions], Env) ->
863
857
  MsVar = mk_var(Ms),
899
893
  trans_bin_call({hipe_bs_primop,Name}, Lbl, Args, [Dst, Base, Offset],
900
894
                 Base, Offset, Env, Instructions);
901
895
trans_fun([{bs_bits_to_bytes2, Bits, Bytes}|Instructions], Env) ->
902
 
  Src = trans_arg(Bits), 
 
896
  Src = trans_arg(Bits),
903
897
  Dst = mk_var(Bytes),
904
898
  [hipe_icode:mk_primop([Dst], 'bsl', [Src, hipe_icode:mk_const(3)])|
905
899
   trans_fun(Instructions,Env)];
950
944
    end,
951
945
  MultIs ++ IsPos ++ [AddI|trans_fun(Instructions, Env)];
952
946
%%--------------------------------------------------------------------
953
 
%% Bit syntax instructions added in R12B-5 (Fall 2008) - PER PLEASE FIX
 
947
%% Bit syntax instructions added in R12B-5 (Fall 2008)
954
948
%%--------------------------------------------------------------------
955
 
%%trans_fun([{test,bs_get_utf8,{f,Lbl},[A1,A2,FF,A4]}|Instructions], Env) ->
956
 
%%trans_fun([{test,bs_skip_utf8,{f,Lbl},[A1,A2,FF]}|Instructions], Env) ->
957
 
%%trans_fun([{test,bs_get_utf16,{f,Lbl},[A1,A2,FF,A4]}|Instructions], Env) ->
958
 
%%trans_fun([{test,bs_skip_utf16,{f,Lbl},[A1,A2,FF]}|Instructions], Env) ->
959
 
%%trans_fun([{test,bs_get_utf32,{f,Lbl},[A1,A2,FF,A4]}|Instructions], Env) ->
960
 
%%trans_fun([{test,bs_skip_utf32,{f,Lbl},[A1,A2,FF]}|Instructions], Env) ->
961
 
%%trans_fun([{bs_utf8_size,{f,Lbl},A2,A3}|Instructions], Env) ->
962
 
%%trans_fun([{bs_put_utf8,{f,Lbl},FF,A3}|Instructions], Env) ->
963
 
%%trans_fun([{bs_utf16_size,{f,Lbl},A2,A3}|Instructions], Env) ->
964
 
%%trans_fun([{bs_put_utf16,{f,Lbl},FF,A3}|Instructions], Env) ->
965
 
%%trans_fun([{bs_put_utf32,{f,Lbl},FF,A3}|Instructions], Env) ->
 
949
trans_fun([{bs_utf8_size,{f,Lbl},A2,A3}|Instructions], Env) ->
 
950
  Bin = trans_arg(A2),
 
951
  Dst = mk_var(A3),
 
952
  trans_op_call({hipe_bs_primop, bs_utf8_size}, Lbl, [Bin], [Dst], Env, Instructions);
 
953
trans_fun([{test,bs_get_utf8,{f,Lbl},[Ms,_Live,{field_flags,_Flags},X]} |
 
954
           Instructions], Env) ->
 
955
  trans_bs_get_or_skip_utf8(Lbl, Ms, X, Instructions, Env);
 
956
trans_fun([{test,bs_skip_utf8,{f,Lbl},[Ms,_Live,{field_flags,_Flags}]} |
 
957
           Instructions], Env) ->
 
958
  trans_bs_get_or_skip_utf8(Lbl, Ms, 'new', Instructions, Env);
 
959
trans_fun([{bs_utf16_size,{f,Lbl},A2,A3}|Instructions], Env) ->
 
960
  Bin = trans_arg(A2),
 
961
  Dst = mk_var(A3),
 
962
  trans_op_call({hipe_bs_primop, bs_utf16_size}, Lbl, [Bin], [Dst], Env, Instructions);
 
963
trans_fun([{test,bs_get_utf16,{f,Lbl},[Ms,_Live,{field_flags,Flags0},X]} |
 
964
           Instructions], Env) ->
 
965
  trans_bs_get_or_skip_utf16(Lbl, Ms, Flags0, X, Instructions, Env);
 
966
trans_fun([{test,bs_skip_utf16,{f,Lbl},[Ms,_Live,{field_flags,Flags0}]} |
 
967
           Instructions], Env) ->
 
968
  trans_bs_get_or_skip_utf16(Lbl, Ms, Flags0, 'new', Instructions, Env);
 
969
trans_fun([{test,bs_get_utf32,{f,Lbl},[Ms,_Live,{field_flags,Flags0},X]} | Instructions], Env) ->
 
970
  trans_bs_get_or_skip_utf32(Lbl, Ms, Flags0, X, Instructions, Env);
 
971
trans_fun([{test,bs_skip_utf32,{f,Lbl},[Ms,_Live,{field_flags,Flags0}]} | Instructions], Env) ->
 
972
  trans_bs_get_or_skip_utf32(Lbl, Ms, Flags0, 'new', Instructions, Env);
966
973
%%--------------------------------------------------------------------
967
974
%%--- Translation of floating point instructions ---
968
975
%%--------------------------------------------------------------------
1338
1345
    end,
1339
1346
  SrcInstrs ++ trans_bin_call({hipe_bs_primop, Name}, 
1340
1347
                             Lbl, [Src|Args], [Offset], Base, Offset, Env2, Instructions);
 
1348
%%----------------------------------------------------------------
 
1349
%% New binary construction instructions added in R12B-5 (Fall 2008).
 
1350
%%----------------------------------------------------------------
 
1351
trans_bin([{bs_put_utf8,{f,Lbl},_FF,A3}|Instructions], Base, Offset, Env) ->
 
1352
  Src = trans_arg(A3),
 
1353
  Args = [Src, Base, Offset],
 
1354
  trans_bin_call({hipe_bs_primop, bs_put_utf8}, Lbl, Args, [Offset], Base, Offset, Env, Instructions);
 
1355
trans_bin([{bs_put_utf16,{f,Lbl},{field_flags,Flags0},A3}|Instructions], Base, Offset, Env) ->
 
1356
  Src = trans_arg(A3),
 
1357
  Args = [Src, Base, Offset],
 
1358
  Flags = resolve_native_endianess(Flags0),
 
1359
  Name = {bs_put_utf16, Flags},
 
1360
  trans_bin_call({hipe_bs_primop, Name}, Lbl, Args, [Offset], Base, Offset, Env, Instructions);
 
1361
trans_bin([{bs_put_utf32,F={f,Lbl},FF={field_flags,_Flags0},A3}|Instructions], Base, Offset, Env) ->
 
1362
  Src = trans_arg(A3),
 
1363
  trans_bin_call({hipe_bs_primop,bs_validate_unicode}, Lbl, [Src], [], Base, Offset, Env,
 
1364
                 [{bs_put_integer,F,{integer,32},1,FF,A3} | Instructions]);
 
1365
%%----------------------------------------------------------------
 
1366
%% Base cases for the end of a binary construction sequence.
 
1367
%%----------------------------------------------------------------
1341
1368
trans_bin([{bs_final2,Src,Dst}|Instructions], _Base, Offset, Env) ->
1342
1369
  [hipe_icode:mk_primop([mk_var(Dst)], {hipe_bs_primop, bs_final}, 
1343
1370
                        [trans_arg(Src),Offset])
1345
1372
trans_bin(Instructions, _Base, _Offset, Env) ->
1346
1373
  trans_fun(Instructions, Env).
1347
1374
 
 
1375
%% this translates bs_get_utf8 and bs_skip_utf8 (get with new unused dst)
 
1376
trans_bs_get_or_skip_utf8(Lbl, Ms, X, Instructions, Env) ->
 
1377
  Dst = mk_var(X),
 
1378
  MsVar = mk_var(Ms),
 
1379
  trans_op_call({hipe_bs_primop,bs_get_utf8}, Lbl, [MsVar], [Dst,MsVar], Env, Instructions).
 
1380
 
 
1381
%% this translates bs_get_utf16 and bs_skip_utf16 (get with new unused dst)
 
1382
trans_bs_get_or_skip_utf16(Lbl, Ms, Flags0, X, Instructions, Env) ->
 
1383
  Dst = mk_var(X),
 
1384
  MsVar = mk_var(Ms),
 
1385
  Flags = resolve_native_endianess(Flags0),
 
1386
  Name = {bs_get_utf16,Flags},
 
1387
  trans_op_call({hipe_bs_primop,Name}, Lbl, [MsVar], [Dst,MsVar], Env, Instructions).
 
1388
 
 
1389
%% this translates bs_get_utf32 and bs_skip_utf32 (get with new unused dst)
 
1390
trans_bs_get_or_skip_utf32(Lbl, Ms, Flags0, X, Instructions, Env) ->
 
1391
  Dst = mk_var(X),
 
1392
  MsVar = mk_var(Ms),
 
1393
  Flags = resolve_native_endianess(Flags0),
 
1394
  {I1,Env1} = trans_one_op_call({hipe_bs_primop,{bs_get_integer,32,Flags}},
 
1395
                                Lbl, [MsVar], [Dst,MsVar], Env),
 
1396
  I1 ++ trans_op_call({hipe_bs_primop,bs_validate_unicode_retract},
 
1397
                      Lbl, [Dst,MsVar], [MsVar], Env1, Instructions).
1348
1398
 
1349
1399
%%-----------------------------------------------------------------------
1350
1400
%% trans_arith(Op, SrcVars, Des, Lab, Env) -> { Icode, NewEnv }
2062
2112
fix_catches([], _HandledCatchLbls) ->
2063
2113
  [].
2064
2114
 
2065
 
fix_catch(Type,Lbl,ContLbl,Code,HandledCatchLbls,Instr) ->
2066
 
  case gb_trees:lookup({Type,Lbl}, HandledCatchLbls) of
 
2115
fix_catch(Type, Lbl, ContLbl, Code, HandledCatchLbls, Instr) ->
 
2116
  TLbl = {Type, Lbl},
 
2117
  case gb_trees:lookup(TLbl, HandledCatchLbls) of
2067
2118
    {value, Catch} when is_integer(Catch) ->
2068
2119
      NewCode = fix_catches(Code, HandledCatchLbls),
2069
2120
      Cont = hipe_icode:label_name(ContLbl),
2077
2128
      %% The rest of the code cannot contain catches with the same label.
2078
2129
      RestOfCode1 = fix_catches(RestOfCode, HandledCatchLbls),
2079
2130
      %% The catched code *can* contain more catches with the same label.
2080
 
      NewHandledCatchLbls = gb_trees:insert({Type,Lbl}, NewCatch,
2081
 
                                            HandledCatchLbls),
 
2131
      NewHandledCatchLbls = gb_trees:insert(TLbl, NewCatch, HandledCatchLbls),
2082
2132
      CatchedCode = fix_catches(CodeToCatch, NewHandledCatchLbls),
2083
2133
      %% The variables which will get the tag, value, and trace.
2084
2134
      Vars = [mk_var({r,0}), mk_var({x,1}), mk_var({x,2})],
2198
2248
 
2199
2249
%% returns the instructions from the closest label
2200
2250
-spec skip_to_label(icode_instrs()) -> icode_instrs().
2201
 
skip_to_label([I|Is]) ->
 
2251
skip_to_label([I|Is] = Instrs) ->
2202
2252
  case I of
2203
 
    #icode_label{} -> [I|Is];
 
2253
    #icode_label{} -> Instrs;
2204
2254
    _ -> skip_to_label(Is)
2205
2255
  end;
2206
2256
skip_to_label([]) ->