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

« back to all changes in this revision

Viewing changes to lib/hipe/rtl/hipe_rtl_primops.erl

  • Committer: Bazaar Package Importer
  • Author(s): Erlang Packagers, Sergei Golovan
  • Date: 2006-12-03 17:07:44 UTC
  • mfrom: (2.1.11 feisty)
  • Revision ID: james.westby@ubuntu.com-20061203170744-rghjwupacqlzs6kv
Tags: 1:11.b.2-4
[ Sergei Golovan ]
Fixed erlang-base and erlang-base-hipe prerm scripts.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%% -*- erlang-indent-level: 2 -*-
2
2
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
3
3
%% Copyright (c) 2001 by Erik Johansson.  All Rights Reserved 
4
 
%% Time-stamp: <2003-04-02 18:06:28 richardc>
5
4
%% ====================================================================
6
 
%%  Filename :  map.erl
7
 
%%  Module   :  map
 
5
%%  Filename :  hipe_rtl_primops.erl
8
6
%%  Purpose  :  
9
7
%%  Notes    : 
10
8
%%  History  :  * 2001-03-15 Erik Johansson (happi@csd.uu.se): 
11
9
%%               Created.
12
 
%%  CVS      :
13
 
%%              $Author: tobiasl $
14
 
%%              $Date: 2003/05/07 17:44:23 $
15
 
%%              $Revision: 1.48 $
16
 
%% ====================================================================
17
 
%%  Exports  :
18
 
%%
19
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
10
%%
 
11
%% $Id$
 
12
%%
20
13
 
21
14
-module(hipe_rtl_primops). 
22
 
-export([gen_primop/3,gen_enter_fun/2]).
23
 
-export([gen_mk_tuple/3]).
24
 
-export([type/2]).
25
 
 
26
 
%%------------------------------------------------------------------------
 
15
 
 
16
-export([gen_primop/4, gen_enter_primop/4, gen_call_builtin/6,
 
17
         gen_enter_builtin/2]).
 
18
 
 
19
%% --------------------------------------------------------------------
27
20
 
28
21
-include("../main/hipe.hrl").
29
 
-include("hipe_icode2rtl.hrl").
 
22
-include("hipe_rtl.hrl").
30
23
-include("hipe_literals.hrl").
31
24
 
32
 
%%------------------------------------------------------------------------
33
 
 
34
 
 
35
 
%% ____________________________________________________________________
 
25
%% --------------------------------------------------------------------
 
26
%% Handling of known MFA builtins that are inline expanded
 
27
 
 
28
gen_call_builtin(Fun, Dst, Args, IsGuard, Cont, Fail) ->
 
29
  case Fun of
 
30
    {erlang,apply,3} ->
 
31
      gen_apply(Dst, Args, Cont, Fail);
 
32
 
 
33
    {erlang,element,2} ->
 
34
      gen_element(Dst, Args, IsGuard, Cont, Fail);
 
35
 
 
36
    {erlang,self,0} ->
 
37
      gen_self(Dst, Cont);
 
38
 
 
39
    {hipe_bifs,in_native,0} ->
 
40
      Dst1 =
 
41
        case Dst of
 
42
          [] -> %% The result is not used.
 
43
            hipe_rtl:mk_new_var();
 
44
          [Dst0] -> Dst0
 
45
        end,
 
46
      [hipe_rtl:mk_load_atom(Dst1, true), hipe_rtl:mk_goto(Cont)];
 
47
    
 
48
    _ -> []    % not a builtin
 
49
  end.
 
50
 
 
51
%% (Recall that enters cannot occur within a catch-region in the same
 
52
%% function, so we don't need to consider fail-continuations here.)
 
53
%% TODO: should we inline expand more functions here? Cf. above.
 
54
gen_enter_builtin(Fun, Args) ->
 
55
  case Fun of
 
56
    {erlang,apply,3} ->
 
57
      gen_enter_apply(Args);
 
58
 
 
59
%% TODO
 
60
%%     {erlang,element,2} ->
 
61
%%       gen_enter_element(Args, IsGuard);
 
62
 
 
63
%% TODO
 
64
%%     {erlang,self,0} ->
 
65
%%       gen_enter_self();
 
66
 
 
67
    {hipe_bifs,in_native,0} ->
 
68
      Dst = hipe_rtl:mk_new_var(),
 
69
      [hipe_rtl:mk_load_atom(Dst, true), hipe_rtl:mk_return([Dst])];
 
70
 
 
71
    _ -> []    % not a builtin
 
72
  end.
 
73
 
 
74
%% --------------------------------------------------------------------
 
75
%% Generate code to jump to in case the inlined function fails.
 
76
 
 
77
gen_fail_code(Fail, Type) -> 
 
78
  gen_fail_code(Fail, Type, false).
 
79
 
 
80
gen_fail_code(Fail, Type, IsGuard) -> 
 
81
  case IsGuard of
 
82
    true when Fail =/= [] ->
 
83
      {Fail, []};  % go directly to target
 
84
    false ->
 
85
      NewLabel =  hipe_rtl:mk_new_label(),
 
86
      NewLabelName = hipe_rtl:label_name(NewLabel),
 
87
      {NewLabelName, [NewLabel | fail_code(Fail, Type)]}
 
88
  end.
 
89
 
 
90
fail_code(Fail, Type) when is_atom(Type) ->
 
91
  Var = hipe_rtl:mk_new_var(),
 
92
  [hipe_rtl:mk_load_atom(Var, Type),
 
93
   hipe_rtl_exceptions:gen_fail(error, [Var], Fail)];
 
94
fail_code(Fail, {Type, Value}) when is_atom(Type) ->
 
95
  Var = hipe_rtl:mk_new_var(),
 
96
  [hipe_rtl:mk_load_atom(Var, Type),
 
97
   hipe_rtl:mk_gctest(3),  % room for a 2-tuple
 
98
   gen_mk_tuple(Var,[Var,Value]),
 
99
   hipe_rtl_exceptions:gen_fail(error, [Var], Fail)].
 
100
 
 
101
fp_fail_code(TmpFailLbl, FailLbl) ->
 
102
  [TmpFailLbl |
 
103
   hipe_rtl_arch:handle_fp_exception() ++
 
104
   [fail_code(FailLbl, badarith)]].
 
105
 
 
106
%% --------------------------------------------------------------------
36
107
%% CALL PRIMOP
37
108
%%
38
 
%% Generate code for primops. This is mostly a dispatch function
39
 
%%
40
 
gen_primop({Op, Dst, Args, Cont, Fail, Annot},
41
 
           {VarMap,  ConstTab},
42
 
           {Options, ExitInfo}) ->
 
109
%% @doc
 
110
%%   Generates RTL code for primops. This is mostly a dispatch function.
 
111
%%   Tail calls to primops (enter_fun, apply, etc.) are not handled here!
 
112
%% @end
 
113
 
 
114
gen_primop({Op,Dst,Args,Cont,Fail}, IsGuard, ConstTab, Options) ->
43
115
  GotoCont = hipe_rtl:mk_goto(Cont),
44
 
  
45
116
  case Op of
46
 
    %% ------------------------------------------------
 
117
    %%
47
118
    %% Binary Syntax
48
119
    %%
49
120
    {hipe_bs_primop, BsOP} ->
50
 
 
51
 
      FailLabel =  hipe_rtl:mk_new_label(),
52
 
      case get(hipe_inline_bs) of
 
121
      {FailLabelName, FailCode} = 
 
122
        gen_fail_code(Fail, badarg, IsGuard),
 
123
      case proplists:get_bool(inline_bs, Options) of
53
124
        true -> 
54
125
          {Code1, NewTab} =
55
126
            hipe_rtl_inline_bs_ops:gen_rtl(BsOP, Args, Dst, Cont,
56
 
                                           hipe_rtl:label_name(FailLabel),
57
 
                                           ConstTab);
58
 
        _ ->
 
127
                                           FailLabelName, ConstTab);
 
128
        false ->
59
129
          {Code1, NewTab} =
60
130
            hipe_rtl_bs_ops:gen_rtl(BsOP, Args, Dst, Cont,
61
 
                                    hipe_rtl:label_name(FailLabel),
62
 
                                    ConstTab)
 
131
                                    FailLabelName, ConstTab)
63
132
      end,
64
 
 
65
 
 
66
 
      FailCode = 
67
 
        case Fail of
68
 
          [] ->
69
 
            hipe_rtl_exceptions:gen_exit_atom(badarg, ExitInfo);
70
 
          _ ->
71
 
            hipe_rtl_exceptions:gen_fail_code(Fail,hipe_rtl:mk_new_var(),
72
 
                                              badarg,  ExitInfo)
73
 
        end,
74
 
      {[Code1,FailLabel,FailCode], VarMap, NewTab};
75
 
 
 
133
      {[Code1,FailCode], NewTab};
 
134
    {hipe_bs_primop2, BsOP} ->
 
135
      {FailLabelName, FailCode} = 
 
136
        gen_fail_code(Fail, badarg, IsGuard),
 
137
      Code1 =
 
138
        hipe_rtl_binary:gen_rtl(BsOP, Dst, Args, Cont, FailLabelName),
 
139
      {[Code1,FailCode], ConstTab};
 
140
    
 
141
    {hipe_bsi_primop, BsOP} ->
 
142
      {FailLabelName, FailCode} = 
 
143
        gen_fail_code(Fail, badarg, IsGuard),
 
144
      Code1 = hipe_rtl_cerl_bs_ops:gen_rtl(BsOP, Args, Dst, Cont,
 
145
                                           FailLabelName),
 
146
      {[Code1,FailCode], ConstTab};
 
147
    
 
148
    %%
 
149
    %% Other primops
 
150
    %%
76
151
    _ ->
77
152
      Code = 
78
153
        case Op of
79
154
          %% Arithmetic
80
155
          '+' ->
81
 
            gen_add_sub_2(Dst, Args, Cont, Fail, Annot, Op, add, ExitInfo);
 
156
            %gen_extra_unsafe_add_2(Dst, Args, Cont);
 
157
            gen_add_sub_2(Dst, Args, Cont, Fail, Op, add);
82
158
          '-' ->
83
 
            gen_add_sub_2(Dst, Args, Cont, Fail, Annot, Op, sub, ExitInfo);
 
159
            gen_add_sub_2(Dst, Args, Cont, Fail, Op, sub);
 
160
          '*' ->
 
161
            %% BIF call: am_Times -> nbif_mul_2 -> erts_mixed_times
 
162
            [hipe_rtl:mk_call(Dst, '*', Args, Cont, Fail, not_remote)];
 
163
          '/' ->
 
164
            %% BIF call: am_Div -> nbif_div_2 -> erts_mixed_div
 
165
            [hipe_rtl:mk_call(Dst, '/', Args, Cont, Fail, not_remote)];
 
166
          'unsafe_add' ->
 
167
            %gen_extra_unsafe_add_2(Dst, Args, Cont);
 
168
            gen_unsafe_add_sub_2(Dst, Args, Cont, Fail, '+', add);
 
169
          'extra_unsafe_add' ->
 
170
            gen_extra_unsafe_add_2(Dst, Args, Cont);
 
171
          'unsafe_sub' ->
 
172
            gen_unsafe_add_sub_2(Dst, Args, Cont, Fail, '-', sub);
 
173
          'extra_unsafe_sub' ->
 
174
            gen_extra_unsafe_sub_2(Dst, Args, Cont);
 
175
          %'unsafe_mul' ->
 
176
          %  gen_unsafe_mul_2(Dst, Args, Cont, Fail, '*');
 
177
          'div' ->
 
178
            %% BIF call: am_div -> nbif_intdiv_2 -> intdiv_2
 
179
            [hipe_rtl:mk_call(Dst, 'div', Args, Cont, Fail, not_remote)];
 
180
          'rem' ->
 
181
            %% BIF call: am_rem -> nbif_rem_2 -> rem_2
 
182
            [hipe_rtl:mk_call(Dst, 'rem', Args, Cont, Fail, not_remote)];
84
183
          'band' ->
85
 
            Dst1 =
86
 
              case Dst of
87
 
                [] -> %% The result is not used.
88
 
                  [hipe_rtl:mk_new_var()];
89
 
                Dst0 -> Dst0
90
 
              end,
91
 
            gen_bitop_2(Dst1, Args, Cont, Fail, Annot, Op, 'and', ExitInfo);
 
184
            gen_bitop_2(Dst, Args, Cont, Fail, Op, 'and');
92
185
          'bor' ->
93
 
            Dst1 =
94
 
              case Dst of
95
 
                [] -> %% The result is not used.
96
 
                  [hipe_rtl:mk_new_var()];
97
 
                Dst0 -> Dst0
98
 
              end,
99
 
            gen_bitop_2(Dst1, Args, Cont, Fail, Annot, Op, 'or', ExitInfo);
 
186
            gen_bitop_2(Dst, Args, Cont, Fail, Op, 'or');
100
187
          'bxor' ->
101
 
            Dst1 =
102
 
              case Dst of
103
 
                [] -> %% The result is not used.
104
 
                  [hipe_rtl:mk_new_var()];
105
 
                Dst0 -> Dst0
106
 
              end,
107
 
            gen_bitop_2(Dst1, Args, Cont, Fail, Annot, Op, 'xor', ExitInfo);
 
188
            gen_bitop_2(Dst, Args, Cont, Fail, Op, 'xor');
108
189
          'bnot' ->
109
 
            Dst1 =
110
 
              case Dst of
111
 
                [] -> %% The result is not used.
112
 
                  [hipe_rtl:mk_new_var()];
113
 
                Dst0 -> Dst0
114
 
              end,
115
 
            gen_bnot_2(Dst1, Args, Cont, Fail, Annot, Op, ExitInfo);
116
 
 
117
 
 
118
 
          %% These are just calls to the bifs...
119
 
%           '*' ->
120
 
%               gen_call_bif(Dst, Args, Cont, Fail, Op, badarith, ExitInfo);
121
 
%           '/' ->
122
 
%               gen_call_bif(Dst, Args, Cont, Fail, Op, badarith, ExitInfo);
123
 
%           'div' ->
124
 
%               gen_call_bif(Dst, Args, Cont, Fail, Op, badarith, ExitInfo);
125
 
%           'rem' ->
126
 
%               gen_call_bif(Dst, Args, Cont, Fail, Op, badarith, ExitInfo);
127
 
%           'bsl' ->
128
 
%               gen_call_bif(Dst, Args, Cont, Fail, Op, badarith, ExitInfo);
129
 
%           'bsr' ->
130
 
%               gen_call_bif(Dst, Args, Cont, Fail, Op, badarith, ExitInfo);
131
 
 
 
190
            gen_bnot_2(Dst, Args, Cont, Fail, Op);
 
191
          'bsr'->
 
192
            %% BIF call: am_bsr -> nbif_bsr_2 -> bsr_2
 
193
            gen_bsr_2(Dst, Args, Cont, Fail, Op);
 
194
            %[hipe_rtl:mk_call(Dst, 'bsr', Args, Cont, Fail, not_remote)];
 
195
          'bsl' -> 
 
196
            %% BIF call: am_bsl -> nbif_bsl_2 -> bsl_2
 
197
            [hipe_rtl:mk_call(Dst, 'bsl', Args, Cont, Fail, not_remote)];
 
198
          'unsafe_band' ->
 
199
            gen_unsafe_bitop_2(Dst, Args, Cont, 'and');
 
200
          'unsafe_bor' -> 
 
201
            gen_unsafe_bitop_2(Dst, Args, Cont, 'or');
 
202
          'unsafe_bxor' ->
 
203
            gen_unsafe_bitop_2(Dst, Args, Cont, 'xor');
 
204
          'unsafe_bnot' ->
 
205
            gen_unsafe_bnot_2(Dst, Args, Cont);
 
206
          'unsafe_bsr' ->
 
207
            gen_unsafe_bsr_2(Dst, Args, Cont);
 
208
          'unsafe_bsl' ->
 
209
            gen_unsafe_bsl_2(Dst, Args, Cont);
132
210
          %% List handling
133
211
          cons ->
134
212
            case Dst of
135
213
              [] -> %% The result is not used.
136
214
                [GotoCont];
137
215
              [Dst1] ->     
138
 
                [gen_cons(Dst1, Args, Options),GotoCont]
 
216
                [gen_cons(Dst1, Args), GotoCont]
139
217
            end;
140
218
          unsafe_hd ->
141
219
            case Dst of
142
220
              [] -> %% The result is not used.
143
221
                [GotoCont];
144
222
              [Dst1] ->   
145
 
                [gen_unsafe_hd(Dst1, Args),GotoCont]
 
223
                [gen_unsafe_hd(Dst1, Args), GotoCont]
146
224
            end;
147
225
          unsafe_tl ->
148
226
            case Dst of
152
230
                [gen_unsafe_tl(Dst1, Args),GotoCont]
153
231
            end;
154
232
 
155
 
 
156
233
          %% Tuple handling
157
234
          mktuple ->
158
235
            case Dst of
159
236
              [] -> %% The result is not used.
160
237
                [GotoCont];
161
238
              [Dst1] ->
162
 
                [gen_mk_tuple(Dst1, Args, Options),GotoCont]
163
 
            end;
164
 
 
165
 
          %% TODO: Remove unused element functions...
166
 
          unsafe_element ->
167
 
            [Index, Tuple] = Args,
168
 
            case Dst of
169
 
              [] -> %% The result is not used.
170
 
                [gen_unsafe_element(hipe_rtl:mk_new_var(), Index, Tuple),GotoCont];
171
 
              [Dst1] ->
172
 
                [gen_unsafe_element(Dst1, Index, Tuple),GotoCont]
173
 
            end;
174
 
          {unsafe_element, N} ->
 
239
                [gen_mk_tuple(Dst1, Args),GotoCont]
 
240
            end;
 
241
          {unsafe_element,N} ->
175
242
            case Dst of
176
243
              [] -> %% The result is not used.
177
244
                [GotoCont];
179
246
                [Tuple] = Args,
180
247
                [gen_unsafe_element(Dst1, hipe_rtl:mk_imm(N), Tuple),GotoCont]
181
248
            end;
182
 
          {unsafe_update_element, N} ->
183
 
            [] = Dst,
 
249
          {unsafe_update_element,N} ->
 
250
            [Dst1] = Dst,
184
251
            [Tuple, Value] = Args,
185
252
            [gen_unsafe_update_element(Tuple, hipe_rtl:mk_imm(N), Value),
 
253
             hipe_rtl:mk_move(Dst1, Tuple),
186
254
             GotoCont];
187
 
          {erlang,element,2} ->
188
 
            Dst1 =
189
 
              case Dst of
190
 
                [] -> %% The result is not used.
191
 
                  hipe_rtl:mk_new_var();
192
 
                [Dst0] -> Dst0
193
 
              end,
194
 
            [Index, Tuple] = Args,
195
 
            [gen_element_2(Dst1, Fail, Index, Tuple, 
196
 
                           Cont, Annot, ExitInfo, [], [])];
197
 
          {erlang,element,2, TypeInfo} ->
 
255
          {element,TypeInfo} ->
198
256
            Dst1 =
199
257
              case Dst of
200
258
                [] -> %% The result is not used.
203
261
              end,
204
262
            [TupleInfo, IndexInfo] = TypeInfo,      
205
263
            [Index, Tuple] = Args,          
206
 
            [gen_element_2(Dst1, Fail, Index, Tuple, 
207
 
                           Cont, Annot, ExitInfo, TupleInfo, IndexInfo)];
208
 
%         element -> %% Obsolete.
209
 
%           [Dst1,  _Flag] = Dst,
210
 
%           [Index, Tuple] = Args,
211
 
%           [gen_element_2(Dst1, Fail, Index, Tuple, 
212
 
%                          Cont, Annot, ExitInfo)];
 
264
            [gen_element_1(Dst1, Index, Tuple, IsGuard, Cont, Fail,
 
265
                           TupleInfo, IndexInfo)];
 
266
 
 
267
          %% Apply-fixarity
 
268
          {apply_N,Arity} ->
 
269
            gen_apply_N(Dst, Arity, Args, Cont, Fail);
213
270
 
214
271
          %% GC test
215
 
          {gc_test, Need} ->
 
272
          {gc_test,Need} ->
216
273
            [hipe_rtl:mk_gctest(Need),GotoCont];
217
274
 
218
275
          %% Process handling.
219
 
          {erlang,self,0} ->
220
 
            case Dst of
221
 
              [] -> %% The result is not used.
222
 
                [GotoCont];
223
 
              [Dst1] ->
224
 
                [load_p_field(Dst1, ?P_ID),
225
 
                 GotoCont]
226
 
            end;
227
276
          redtest ->
228
277
            [gen_redtest(1),GotoCont];
 
278
 
229
279
          %% Receives
230
 
          get_msg ->
231
 
            hipe_rtl_arch:call_bif(Dst, get_msg, [], Cont, Fail);
 
280
          check_get_msg ->
 
281
            gen_check_get_msg(Dst, GotoCont, Fail);
232
282
          next_msg ->
233
 
            hipe_rtl_arch:call_bif(Dst, next_msg, [], Cont, Fail);
 
283
            gen_next_msg(Dst, GotoCont);
234
284
          select_msg ->
235
 
            hipe_rtl_arch:call_bif(Dst, select_msg, [], Cont, Fail);
 
285
            gen_select_msg(Dst, Cont);
236
286
          clear_timeout ->
237
 
            NewArgs = Args, 
238
 
            hipe_rtl:mk_call(Dst, Op, NewArgs, c, Cont, Fail);
 
287
            gen_clear_timeout(Dst, GotoCont);
 
288
          set_timeout ->
 
289
            %% BIF call: am_set_timeout -> nbif_set_timeout -> hipe_set_timeout
 
290
            [hipe_rtl:mk_call(Dst, set_timeout, Args, Cont, Fail, not_remote)];
239
291
          suspend_msg ->
240
 
            hipe_rtl:mk_call(Dst, Op, Args, c, Cont, Fail);
241
 
 
 
292
            gen_suspend_msg(Dst, Cont);
242
293
 
243
294
          %% Closures
244
295
          call_fun ->
245
 
            gen_call_fun(Dst, Args, Cont, Fail, ExitInfo);
 
296
            gen_call_fun(Dst, Args, Cont, Fail);
246
297
          {mkfun,MFA,MagicNum,Index} ->
247
298
            case Dst of
248
299
              [] -> %% The result is not used.
249
300
                [GotoCont];
250
301
              _ ->
251
 
                [gen_mkfun(Dst, MFA, MagicNum, Index, Args, Fail),GotoCont]
 
302
                [gen_mkfun(Dst, MFA, MagicNum, Index, Args), GotoCont]
252
303
            end;
253
 
 
254
 
          {closure_element, N} ->
 
304
          {closure_element,N} ->
255
305
            case Dst of
256
306
              [] -> %% The result is not used.
257
307
                [GotoCont];
261
311
                 GotoCont]
262
312
            end;
263
313
 
264
 
          {hipe_bifs, in_native, 0} ->
265
 
            Dst1 =
266
 
              case Dst of
267
 
                [] -> %% The result is not used.
268
 
                  hipe_rtl:mk_new_var();
269
 
                [Dst0] -> Dst0
270
 
              end,
271
 
            [ hipe_rtl:mk_load_atom(Dst1, true),
272
 
              GotoCont];
273
 
          {erlang, apply, 3} ->
274
 
            %%  TODO:    gen_apply(Dst,Args, Cont, Fail, ExitInfo);
275
 
            [hipe_rtl:mk_call(Dst, 
276
 
                              {hipe_internal, apply, 3}, 
277
 
                              Args, 
278
 
                              c,
279
 
                              Cont, Fail)];
280
 
 
281
 
          %% Floating point stuff.
282
 
 
 
314
          %% Floating point instructions.
283
315
          fp_add ->
284
316
            [Arg1, Arg2] = Args,
285
317
            case Dst of
288
320
              [Dst1] ->
289
321
                hipe_rtl:mk_fp(Dst1, Arg1, 'fadd', Arg2)
290
322
            end;
291
 
 
292
323
          fp_sub ->
293
324
            [Arg1, Arg2] = Args,
294
325
            case Dst of
297
328
              [Dst1] ->
298
329
                hipe_rtl:mk_fp(Dst1, Arg1, 'fsub', Arg2)
299
330
            end;          
300
 
 
301
331
          fp_mul ->
302
332
            [Arg1, Arg2] = Args,
303
333
            case Dst of
306
336
              [Dst1] ->
307
337
                hipe_rtl:mk_fp(Dst1, Arg1, 'fmul', Arg2)
308
338
            end;
309
 
 
310
339
          fp_div ->
311
340
            [Arg1, Arg2] = Args,
312
341
            case Dst of
315
344
              [Dst1] ->
316
345
                hipe_rtl:mk_fp(Dst1, Arg1, 'fdiv', Arg2)
317
346
            end;          
318
 
 
319
347
          fnegate ->
320
348
            [Arg] = Args,
321
349
            case Dst of
324
352
              [Dst1] ->
325
353
                hipe_rtl:mk_fp_unop(Dst1, Arg, 'fchs')
326
354
            end;          
327
 
 
328
355
          fclearerror ->
329
356
            gen_fclearerror();
330
 
 
331
357
          fcheckerror ->
332
 
            gen_fcheckerror(Cont, Fail, ExitInfo);
333
 
 
 
358
            gen_fcheckerror(Cont, Fail);
334
359
          conv_to_float ->
335
360
            case Dst of
336
361
              [] ->
337
 
                gen_conv_to_float(hipe_rtl:mk_new_fpreg(), Args, Cont, Fail, ExitInfo);
 
362
                gen_conv_to_float(hipe_rtl:mk_new_fpreg(), Args, Cont, Fail);
338
363
              [Dst1] ->
339
 
                gen_conv_to_float(Dst1, Args, Cont, Fail, ExitInfo)
 
364
                gen_conv_to_float(Dst1, Args, Cont, Fail)
340
365
            end;
341
 
 
342
366
          unsafe_untag_float ->
343
367
            [Arg] = Args,
344
368
            case Dst of
348
372
              [Dst1]->
349
373
                hipe_tagscheme:unsafe_untag_float(Dst1, Arg)
350
374
            end;
351
 
          
352
375
          unsafe_tag_float ->
353
376
            [Arg] = Args,
354
377
            case Dst of
355
378
              [] ->
356
 
                hipe_tagscheme:unsafe_tag_float(hipe_rtl:mk_new_var(),
357
 
                                                Arg, Options);
 
379
                hipe_tagscheme:unsafe_tag_float(hipe_rtl:mk_new_var(), Arg);
358
380
              [Dst1]->
359
 
                hipe_tagscheme:unsafe_tag_float(Dst1, Arg, Options)
 
381
                hipe_tagscheme:unsafe_tag_float(Dst1, Arg)
360
382
            end;
361
383
 
 
384
          %% Only names listed above are accepted! MFA:s are not primops!
362
385
          _ ->
363
 
            generic_primop(Dst, Op, Args, Cont, Fail, ExitInfo)
 
386
            erlang:error({bad_primop, Op})
364
387
        end,
365
 
      {Code, VarMap, ConstTab}
366
 
  end.
367
 
 
368
 
 
369
 
%% ____________________________________________________________________
370
 
%% 
371
 
%%
372
 
%% Generate code for a generic call to a bif.
373
 
generic_primop(Dsts, Op, Args, Continuation, Fail, ExitInfo) ->
374
 
  %% Get arity and name
375
 
  {Arity, Name} = 
376
 
    case Op of 
377
 
      {_Mod,BifName,A} -> %% An ordinary MFA
378
 
        {A, BifName};
379
 
      _ -> %% Some internal primop with just a name.
380
 
        {length(Args),Op}
381
 
    end,
382
 
 
383
 
  %% Test if the bif can fail
384
 
  Fails = hipe_bif:fails(Arity,Name),
385
 
  if Fails =:= false ->
386
 
      %% The bif can't fail just call it.
387
 
      [hipe_rtl:mk_call(Dsts, Op , Args, c, Continuation, [])];
388
 
     true ->
389
 
      %% The bif can fail, call it and test.
390
 
      failing_primop(Dsts, Op, Args, Continuation, Fail, ExitInfo)
391
 
  end.
392
 
 
393
 
%% Generate code for a bif that can fail.
394
 
failing_primop(Dsts, Op, Args, Continuation, Fail, _ExitInfo) ->
395
 
  [hipe_rtl:mk_call(Dsts, Op, Args, c, Continuation, Fail)].
396
 
 
397
 
 
398
 
%% Generate code for a bif that can fail.
399
 
gen_call_bif(Res, Args, Cont, Fail, Op, _ExitReason, _ExitInfo) ->
400
 
  [hipe_rtl:mk_call(Res, Op, Args, c, Cont, Fail)].
401
 
 
402
 
 
403
 
 
404
 
%% ____________________________________________________________________
405
 
%% 
406
 
 
407
 
%% ____________________________________________________________________
 
388
      {Code, ConstTab}
 
389
  end.
 
390
 
 
391
gen_enter_primop({Op, Args}, IsGuard, ConstTab, Options) ->
 
392
  case Op of
 
393
    enter_fun ->
 
394
      %% Tail-call to a closure must preserve tail-callness!
 
395
      %% (Passing Continuation = [] to gen_call_fun/5 does this.)
 
396
      Code = gen_call_fun([], Args, [], []),
 
397
      {Code, ConstTab};
 
398
 
 
399
    {apply_N,Arity} ->
 
400
      %% Tail-call to a closure must preserve tail-callness!
 
401
      %% (Passing Continuation = [] to gen_apply_N/5 does this.)
 
402
      Code = gen_apply_N([], Arity, Args, [], []),
 
403
      {Code,  ConstTab};
 
404
 
 
405
    _ ->
 
406
      %% All other primop tail calls are converted to call + return.
 
407
      Dst = [hipe_rtl:mk_new_var()],
 
408
      OkLab = hipe_rtl:mk_new_label(),
 
409
      {Code,ConstTab1} = 
 
410
        gen_primop({Op,Dst,Args,hipe_rtl:label_name(OkLab),[]}, 
 
411
                   IsGuard, ConstTab, Options),
 
412
      {Code ++ [OkLab, hipe_rtl:mk_return(Dst)], ConstTab1}
 
413
  end.
 
414
 
 
415
 
 
416
%% --------------------------------------------------------------------
408
417
%% ARITHMETIC
409
418
%%
410
419
 
412
421
%% Inline addition & subtraction
413
422
%%
414
423
 
415
 
gen_add_sub_2(Dst, Args, Cont, Fail, _Annot, Op, AluOp, ExitInfo) ->
 
424
gen_add_sub_2(Dst, Args, Cont, Fail, Op, AluOp) ->
416
425
  [Arg1, Arg2] = Args,
417
426
  GenCaseLabel = hipe_rtl:mk_new_label(),
418
427
  case Dst of
419
428
    [] ->
420
 
      gen_op_general_case(hipe_rtl:mk_new_var(),
421
 
                          Op, Args, Cont, Fail, GenCaseLabel, ExitInfo);
 
429
      [hipe_tagscheme:test_two_fixnums(Arg1, Arg2,
 
430
                                       hipe_rtl:label_name(GenCaseLabel))|
 
431
       gen_op_general_case(hipe_rtl:mk_new_var(),
 
432
                           Op, Args, Cont, Fail, GenCaseLabel)];
422
433
    [Res] ->
423
434
      [hipe_tagscheme:test_two_fixnums(Arg1, Arg2,
424
435
                                       hipe_rtl:label_name(GenCaseLabel)),
425
436
       hipe_tagscheme:fixnum_addsub(AluOp, Arg1, Arg2, Res, GenCaseLabel)|
426
 
       gen_op_general_case(Res,Op, Args, Cont, Fail, GenCaseLabel, ExitInfo)]
427
 
  end.
428
 
 
429
 
 
430
 
gen_op_general_case(Res, Op, Args, Cont, Fail, GenCaseLabel, ExitInfo) ->
 
437
       gen_op_general_case(Res,Op, Args, Cont, Fail, GenCaseLabel)]
 
438
  end.
 
439
 
 
440
gen_unsafe_add_sub_2(Dst, Args, Cont, Fail, Op, AluOp) ->
 
441
  [Arg1, Arg2] = Args,
 
442
  case Dst of
 
443
    [] ->      
 
444
      [hipe_rtl:mk_goto(Cont)];
 
445
    [Res] ->
 
446
      case Fail of
 
447
        []->
 
448
          GenCaseLabel = hipe_rtl:mk_new_label(),
 
449
          [hipe_tagscheme:fixnum_addsub(AluOp, Arg1, Arg2, Res, GenCaseLabel)|
 
450
           gen_op_general_case(Res,Op, Args, Cont, Fail, GenCaseLabel)];
 
451
        _ ->
 
452
          [hipe_tagscheme:fixnum_addsub(AluOp, Arg1, Arg2, Res, 
 
453
                                        hipe_rtl:mk_label(Fail))]
 
454
      end
 
455
  end.
 
456
 
 
457
gen_extra_unsafe_add_2(Dst, Args, Cont) ->
 
458
  [Arg1, Arg2] = Args,
 
459
  case Dst of
 
460
    [] ->      
 
461
      [hipe_rtl:mk_goto(Cont)];
 
462
    [Res] ->
 
463
      hipe_tagscheme:unsafe_fixnum_add(Arg1, Arg2, Res)
 
464
  end.
 
465
 
 
466
gen_extra_unsafe_sub_2(Dst, Args, Cont) ->
 
467
  [Arg1, Arg2] = Args,
 
468
  case Dst of
 
469
    [] ->      
 
470
      [hipe_rtl:mk_goto(Cont)];
 
471
    [Res] ->
 
472
      hipe_tagscheme:unsafe_fixnum_sub(Arg1, Arg2, Res)
 
473
  end.
 
474
 
 
475
gen_op_general_case(Res, Op, Args, Cont, Fail, GenCaseLabel) ->
431
476
  [hipe_rtl:mk_goto(Cont),
432
477
   GenCaseLabel,
433
 
   gen_call_bif([Res], Args, Cont, Fail, Op, badarith, ExitInfo)].
 
478
   hipe_rtl:mk_call([Res], Op, Args, Cont, Fail, not_remote)].
434
479
 
435
480
%%
436
481
%% We don't inline multiplication at the moment
437
482
%%
438
483
 
439
 
%%gen_mul_2([Res], Args, Cont, Fail, Annot, Op, ExitInfo) ->
440
 
%%   [Arg1, Arg2] = Args,
441
 
%%   GenCaseLabel = hipe_rtl:mk_new_label(),
442
 
%%   [hipe_tagscheme:test_two_fixnums(Arg1, Arg2,
443
 
%%                                  hipe_rtl:label_name(GenCaseLabel)),
444
 
%%    hipe_tagscheme:fixnum_mul(Arg1, Arg2, Res, GenCaseLabel)|
445
 
%%    gen_op_general_case(Res, Op, Args, Cont, Fail, GenCaseLabel, ExitInfo)].
 
484
%% gen_unsafe_mul_2([Res], Args, Cont, Fail, Op) ->
 
485
%%    [Arg1, Arg2] = Args,
 
486
%%    GenCaseLabel = hipe_rtl:mk_new_label(),
 
487
%%    [hipe_tagscheme:test_two_fixnums(Arg1, Arg2,
 
488
%%                                  hipe_rtl:label_name(GenCaseLabel)),
 
489
%%     hipe_tagscheme:fixnum_mul(Arg1, Arg2, Res, GenCaseLabel)|
 
490
%%     gen_op_general_case(Res, Op, Args, Cont, Fail, GenCaseLabel)].
446
491
 
447
492
%%
448
493
%% Inline bitoperations.
450
495
%% The shift operations are too expensive to inline.
451
496
%%
452
497
 
453
 
gen_bitop_2([Res], Args, Cont, Fail, _Annot, Op, BitOp, ExitInfo) ->
454
 
  [Arg1, Arg2] = Args,
455
 
  GenCaseLabel = hipe_rtl:mk_new_label(),
456
 
 
457
 
  [hipe_tagscheme:test_two_fixnums(Arg1, Arg2,
458
 
                                   hipe_rtl:label_name(GenCaseLabel)),
459
 
   hipe_tagscheme:fixnum_andorxor(BitOp, Arg1, Arg2, Res)|
460
 
   gen_op_general_case(Res, Op, Args, Cont, Fail, GenCaseLabel, ExitInfo)].
 
498
gen_bitop_2(Res, Args, Cont, Fail, Op, BitOp) ->
 
499
  [Arg1, Arg2] = Args,
 
500
  GenCaseLabel = hipe_rtl:mk_new_label(),
 
501
  case Res of
 
502
    [] -> %% The result is not used.
 
503
      [hipe_tagscheme:test_two_fixnums(Arg1, Arg2,
 
504
                                       hipe_rtl:label_name(GenCaseLabel))|
 
505
       gen_op_general_case(hipe_rtl:mk_new_var(),
 
506
                           Op, Args, Cont, Fail, GenCaseLabel)];        
 
507
    [Res0] -> 
 
508
      [hipe_tagscheme:test_two_fixnums(Arg1, Arg2,
 
509
                                       hipe_rtl:label_name(GenCaseLabel)),
 
510
       hipe_tagscheme:fixnum_andorxor(BitOp, Arg1, Arg2, Res0)|
 
511
       gen_op_general_case(Res0, Op, Args, Cont, Fail, GenCaseLabel)]
 
512
  end.
 
513
  
 
514
gen_unsafe_bitop_2(Res, Args, Cont, BitOp) ->
 
515
  case Res of
 
516
    [] -> %% The result is not used.
 
517
      [hipe_rtl:mk_goto(Cont)];
 
518
    [Res0] -> 
 
519
      [Arg1, Arg2] = Args,
 
520
      [hipe_tagscheme:fixnum_andorxor(BitOp, Arg1, Arg2, Res0),
 
521
       hipe_rtl:mk_goto(Cont)]
 
522
  end.
 
523
 
 
524
gen_bsr_2(Res, Args, Cont, Fail, Op) ->
 
525
  [Arg1, Arg2] = Args,
 
526
  GenCaseLabel = hipe_rtl:mk_new_label(),
 
527
  case hipe_rtl:is_imm(Arg2) of
 
528
    true ->
 
529
      Val =  hipe_tagscheme:fixnum_val(hipe_rtl:imm_value(Arg2)),
 
530
      Limit = ?bytes_to_bits(hipe_rtl_arch:word_size()),
 
531
      if 
 
532
        Val < Limit, Val >= 0 ->
 
533
          case Res of
 
534
            [] ->
 
535
              [hipe_tagscheme:test_fixnum(Arg1,
 
536
                                          hipe_rtl:label_name(Cont),
 
537
                                          hipe_rtl:label_name(GenCaseLabel),
 
538
                                          0.99),
 
539
               gen_op_general_case(hipe_rtl:mk_new_var(), Op, Args, Cont, Fail,
 
540
                                   GenCaseLabel)];
 
541
            [Res0] ->
 
542
              FixLabel = hipe_rtl:mk_new_label(),
 
543
              [hipe_tagscheme:test_fixnum(Arg1,
 
544
                                          hipe_rtl:label_name(FixLabel),
 
545
                                          hipe_rtl:label_name(GenCaseLabel),
 
546
                                          0.99),
 
547
               FixLabel,
 
548
               hipe_tagscheme:fixnum_bsr(Arg1, Arg2, Res0),
 
549
               gen_op_general_case(Res0, Op, Args, Cont, Fail, GenCaseLabel)]
 
550
          end;
 
551
        true ->
 
552
          [hipe_rtl:mk_call(Res, 'bsr', Args, Cont, Fail, not_remote)]
 
553
      end;
 
554
    false ->
 
555
      [hipe_rtl:mk_call(Res, 'bsr', Args, Cont, Fail, not_remote)]
 
556
  end.
 
557
 
 
558
gen_unsafe_bsr_2(Res, Args, Cont) ->
 
559
  case Res of
 
560
    [] -> %% The result is not used.
 
561
      [hipe_rtl:mk_goto(Cont)];
 
562
    [Res0] ->  
 
563
      [Arg1, Arg2] = Args,
 
564
      [hipe_tagscheme:fixnum_bsr(Arg1, Arg2, Res0),
 
565
       hipe_rtl:mk_goto(Cont)]
 
566
  end.
 
567
 
 
568
gen_unsafe_bsl_2(Res, Args, Cont) ->
 
569
  case Res of
 
570
    [] -> %% The result is not used.
 
571
      [hipe_rtl:mk_goto(Cont)];
 
572
    [Res0] ->  
 
573
      [Arg1, Arg2] = Args,
 
574
      [hipe_tagscheme:fixnum_bsl(Arg1, Arg2, Res0),
 
575
       hipe_rtl:mk_goto(Cont)]
 
576
  end.
461
577
 
462
578
%%
463
579
%% Inline not.
464
580
%%
465
581
 
466
 
gen_bnot_2([Res], Args, Cont, Fail, _Annot, Op, ExitInfo) ->
 
582
gen_bnot_2(Res, Args, Cont, Fail, Op) ->
467
583
  [Arg] = Args,
468
 
  FixLabel = hipe_rtl:mk_new_label(),
469
 
  OtherLabel = hipe_rtl:mk_new_label(),
470
 
 
471
 
  [hipe_tagscheme:test_fixnum(Arg, hipe_rtl:label_name(FixLabel),
472
 
                              hipe_rtl:label_name(OtherLabel), 0.99),
473
 
   FixLabel,
474
 
   hipe_tagscheme:fixnum_not(Arg, Res),
475
 
   gen_op_general_case(Res, Op, Args, Cont, Fail, OtherLabel, ExitInfo)
476
 
  ].
477
 
 
478
 
 
479
 
%% ____________________________________________________________________
 
584
  GenCaseLabel = hipe_rtl:mk_new_label(),
 
585
  case Res of
 
586
    [] -> %% The result is not used.
 
587
      [hipe_tagscheme:test_fixnum(Arg, hipe_rtl:label_name(Cont),
 
588
                                  hipe_rtl:label_name(GenCaseLabel), 0.99),
 
589
       gen_op_general_case(hipe_rtl:mk_new_var(), Op, Args, Cont, Fail, 
 
590
                           GenCaseLabel)];
 
591
    
 
592
    [Res0] -> 
 
593
      FixLabel = hipe_rtl:mk_new_label(),
 
594
      [hipe_tagscheme:test_fixnum(Arg, hipe_rtl:label_name(FixLabel),
 
595
                                  hipe_rtl:label_name(GenCaseLabel), 0.99),
 
596
       FixLabel,
 
597
       hipe_tagscheme:fixnum_not(Arg, Res0),
 
598
       gen_op_general_case(Res0, Op, Args, Cont, Fail, GenCaseLabel)]
 
599
  end.
 
600
 
 
601
gen_unsafe_bnot_2(Res, Args, Cont) ->
 
602
  case Res of
 
603
    [] -> %% The result is not used.
 
604
      [hipe_rtl:mk_goto(Cont)];
 
605
    [Res0] ->  
 
606
      [Arg1] = Args,
 
607
      [hipe_tagscheme:fixnum_not(Arg1, Res0),
 
608
       hipe_rtl:mk_goto(Cont)]
 
609
  end.
 
610
 
 
611
 
 
612
%% --------------------------------------------------------------------
480
613
%% 
481
614
 
482
615
%%
483
616
%% Inline cons
484
617
%%
485
618
 
486
 
gen_cons(Dst, [Arg1, Arg2], Options) ->
 
619
gen_cons(Dst, [Arg1, Arg2]) ->
487
620
  Tmp = hipe_rtl:mk_new_reg(),
488
621
  {GetHPInsn, HP, PutHPInsn} = hipe_rtl_arch:heap_pointer(),
489
 
  Code = 
490
 
    [
491
 
     GetHPInsn,
492
 
     hipe_rtl:mk_store(HP, hipe_rtl:mk_imm(0), Arg1),
493
 
     hipe_rtl:mk_store(HP, hipe_rtl:mk_imm(4), Arg2),
494
 
     hipe_rtl:mk_move(Tmp, HP),
495
 
     hipe_tagscheme:tag_cons(Dst, Tmp),
496
 
     hipe_rtl:mk_alu(HP, HP, add, hipe_rtl:mk_imm(8)),
497
 
     PutHPInsn],
498
 
  case ?AddGC(Options) of
499
 
    true -> [hipe_rtl:mk_gctest(2)|Code];
500
 
    false -> Code
501
 
  end.
 
622
  WordSize = hipe_rtl_arch:word_size(),
 
623
  HeapNeed = 2*WordSize,
 
624
  [GetHPInsn,
 
625
   hipe_rtl:mk_store(HP, hipe_rtl:mk_imm(0), Arg1),
 
626
   hipe_rtl:mk_store(HP, hipe_rtl:mk_imm(WordSize), Arg2),
 
627
   hipe_rtl:mk_move(Tmp, HP),
 
628
   hipe_tagscheme:tag_cons(Dst, Tmp),
 
629
   hipe_rtl:mk_alu(HP, HP, add, hipe_rtl:mk_imm(HeapNeed)),
 
630
   PutHPInsn].
502
631
 
503
632
%% %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
504
 
%% ____________________________________________________________________
505
 
%%
 
633
%% --------------------------------------------------------------------
506
634
%% Handling of closures...
507
 
%% ____________________________________________________________________
 
635
%% --------------------------------------------------------------------
508
636
 
509
 
%% ____________________________________________________________________
 
637
%% --------------------------------------------------------------------
510
638
%% gen_mkfun
511
639
%%
512
640
%%    The gc_test should have expanded to
513
641
%%    unsigned needed = ERL_FUN_SIZE + num_free;
514
642
%%    ErlFunThing* funp = (ErlFunThing *) HAlloc(p, needed);
515
643
%%
516
 
%% The code generated should do the eq of:
 
644
%% The code generated should do the equivalent of:
517
645
%%  Copy arguments to the fun thing
518
646
%%    Eterm* hp = funp->env;
519
647
%%    for (i = 0; i < num_free; i++) {
536
664
%%  Tag the thing
537
665
%%    return make_fun(funp);
538
666
%%
539
 
gen_mkfun([Dst], {Mod,FunId,Arity}, MagicNr, Index, FreeVars, _Fail) ->
 
667
gen_mkfun([Dst], {Mod,FunId,Arity}, MagicNr, Index, FreeVars) ->
540
668
  {GetHPInsn, HP, PutHPInsn} = hipe_rtl_arch:heap_pointer(),
541
669
  NumFree = length(FreeVars),
542
670
 
566
694
 
567
695
  %%  Tag the thing and increase the heap_pointer.
568
696
  %%    make_fun(funp);
569
 
  TagCode = [hipe_tagscheme:tag_fun(Dst, HP),
 
697
  WordSize�= hipe_rtl_arch:word_size(),
 
698
  HeapNeed = (?ERL_FUN_SIZE + NumFree) * WordSize,
 
699
  TagCode = [hipe_tagscheme:tag_fun(Dst, HP), 
570
700
             %%  AdjustHPCode 
571
 
             hipe_rtl:mk_alu(HP, HP, add,
572
 
                             hipe_rtl:mk_imm((?ERL_FUN_SIZE + NumFree) * 4)),
 
701
             hipe_rtl:mk_alu(HP, HP, add, hipe_rtl:mk_imm(HeapNeed)),
573
702
             PutHPInsn],
574
 
 
575
703
  [[GetHPInsn | CopyFreeVarsCode], SkeletonCode, LinkCode, TagCode].
576
704
 
577
705
 
586
714
  %%    funp->native_code = fe->native_code;
587
715
  %%  And creates a fe (at load time).
588
716
  FeVar = hipe_rtl:mk_new_reg(),
589
 
  PidVar = hipe_rtl:mk_new_reg(),
 
717
  PidVar = hipe_rtl:mk_new_reg_gcsafe(),
590
718
  NativeVar = hipe_rtl:mk_new_reg(),
591
 
  RefcVar = hipe_rtl:mk_new_reg(),
592
719
 
593
720
  [hipe_rtl:mk_load_address(FeVar, {FunName, MagicNr, Index}, closure),
594
721
   store_struct_field(FunP, ?EFT_FE, FeVar),
597
724
 
598
725
   store_struct_field(FunP, ?EFT_ARITY, hipe_rtl:mk_imm(Arity-NumFree)),
599
726
 
600
 
   load_struct_field(RefcVar, FeVar, ?EFE_REFC),
601
 
   hipe_rtl:mk_alu(RefcVar, RefcVar, add, hipe_rtl:mk_imm(1)),
602
 
   store_struct_field(FeVar, ?EFE_REFC, RefcVar),
 
727
   gen_inc_refc(FeVar, ?EFE_REFC),
603
728
 
604
729
   store_struct_field(FunP, ?EFT_NUM_FREE, hipe_rtl:mk_imm(NumFree)),
605
730
   load_p_field(PidVar, ?P_ID),
606
731
   store_struct_field(FunP, ?EFT_CREATOR, PidVar),
607
 
   store_struct_field(FunP, ?EFT_THING, 
608
 
                      hipe_tagscheme:mk_fun_header())].
609
 
 
610
 
 
611
 
-ifdef(HEAP_ARCH_PRIVATE).
 
732
   store_struct_field(FunP, ?EFT_THING, hipe_tagscheme:mk_fun_header())].
 
733
 
 
734
gen_inc_refc(Ptr, Offset) ->
 
735
  case ?ERTS_IS_SMP of
 
736
    0 -> gen_inc_refc_notsmp(Ptr, Offset);
 
737
    1 -> gen_inc_refc_smp(Ptr, Offset)
 
738
  end.
 
739
 
 
740
gen_inc_refc_notsmp(Ptr, Offset) ->
 
741
  Refc = hipe_rtl:mk_new_reg(),
 
742
  [load_struct_field(Refc, Ptr, Offset, int32),
 
743
   hipe_rtl:mk_alu(Refc, Refc, add, hipe_rtl:mk_imm(1)),
 
744
   store_struct_field(Ptr, Offset, Refc, int32)].
 
745
 
 
746
gen_inc_refc_smp(Ptr, Offset) ->
 
747
  Refc = hipe_rtl:mk_new_reg(),
 
748
  [hipe_rtl:mk_alu(Refc, Ptr, 'add', hipe_rtl:mk_imm(Offset)),
 
749
   hipe_rtl:mk_call([], 'atomic_inc', [Refc], [], [], not_remote)].
 
750
 
612
751
gen_link_closure(FUNP) ->
 
752
  case ?P_OFF_HEAP_FUNS of
 
753
    [] -> gen_link_closure_non_private(FUNP);
 
754
    _ -> gen_link_closure_private(FUNP)
 
755
  end.
 
756
 
 
757
gen_link_closure_private(FUNP) ->
613
758
  %% Link to the process off_heap.funs list
614
759
  %%   funp->next = p->off_heap.funs;
615
760
  %%   p->off_heap.funs = funp;
618
763
  [load_p_field(FunsVar,?P_OFF_HEAP_FUNS),
619
764
   hipe_rtl:mk_store(FUNP, hipe_rtl:mk_imm(?EFT_NEXT), FunsVar),
620
765
   store_p_field(FUNP,?P_OFF_HEAP_FUNS)].
621
 
-endif.
622
766
 
623
 
-ifdef(HEAP_ARCH_SHARED).
624
 
gen_link_closure(FUNP) -> [].
625
 
-endif.
 
767
gen_link_closure_non_private(_FUNP) -> [].
626
768
 
627
769
load_p_field(Dst,Offset) ->
628
770
  hipe_rtl_arch:pcb_load(Dst, Offset).
635
777
load_struct_field(Dest, StructP, Offset) ->
636
778
  hipe_rtl:mk_load(Dest, StructP, hipe_rtl:mk_imm(Offset)).
637
779
 
 
780
store_struct_field(StructP, Offset, Src, int32) ->
 
781
  hipe_rtl:mk_store(StructP, hipe_rtl:mk_imm(Offset), Src, int32).
 
782
 
 
783
load_struct_field(Dest, StructP, Offset, int32) ->
 
784
  hipe_rtl:mk_load(Dest, StructP, hipe_rtl:mk_imm(Offset), int32, signed).
 
785
 
638
786
gen_free_vars(Vars, HPReg) ->
639
 
  HPVar = hipe_rtl:mk_new_var(),  
 
787
  HPVar = hipe_rtl:mk_new_var(),
 
788
  WordSize�= hipe_rtl_arch:word_size(),
640
789
  [hipe_rtl:mk_alu(HPVar, HPReg, add, hipe_rtl:mk_imm(?EFT_ENV)) |
641
 
   gen_free_vars(Vars, HPVar, 0, [])].
 
790
   gen_free_vars(Vars, HPVar, 0, WordSize, [])].
642
791
 
643
 
gen_free_vars([Var|Vars], EnvPVar, Offset, AccCode) ->
 
792
gen_free_vars([Var|Vars], EnvPVar, Offset, WordSize, AccCode) ->
644
793
  Code = hipe_rtl:mk_store(EnvPVar, hipe_rtl:mk_imm(Offset), Var),
645
 
  gen_free_vars(Vars, EnvPVar, Offset + 4, [Code|AccCode]);
646
 
gen_free_vars([], _, _, AccCode) -> AccCode.
 
794
  gen_free_vars(Vars, EnvPVar, Offset + WordSize, WordSize,
 
795
                [Code|AccCode]);
 
796
gen_free_vars([], _, _, _, AccCode) -> AccCode.
647
797
 
648
798
%% ------------------------------------------------------------------
649
799
%%
650
 
%% enter_fun and call_fun
651
 
%%
652
 
gen_enter_fun(Args, ExitInfo) ->
653
 
  gen_call_fun([], Args, [], [], ExitInfo).
 
800
%% call_fun (also handles enter_fun when Continuation = [])
654
801
 
655
 
gen_call_fun(Dst, ArgsAndFun, Continuation, Fail, ExitInfo) ->  
 
802
gen_call_fun(Dst, ArgsAndFun, Continuation, Fail) ->  
656
803
  NAddressReg = hipe_rtl:mk_new_reg(),
657
 
  ArityReg = hipe_rtl:mk_new_reg(),
658
 
  BadFunLab =  hipe_rtl:mk_new_label(),
659
 
  BadArityLab =  hipe_rtl:mk_new_label(),
660
 
  [Fun|Args] = lists:reverse(ArgsAndFun),
661
 
 
662
 
  FailCode = hipe_rtl_exceptions:gen_funcall_fail(Fail, Fun, BadFunLab,
663
 
                                                  BadArityLab, ExitInfo),
 
804
  ArityReg = hipe_rtl:mk_new_reg_gcsafe(),
 
805
  [Fun|RevArgs] = lists:reverse(ArgsAndFun),
 
806
 
 
807
  %% {BadFunLabName, BadFunCode} = gen_fail_code(Fail, {badfun, Fun}),
 
808
  Args = lists:reverse(RevArgs),
 
809
  NonClosureLabel = hipe_rtl:mk_new_label(),
 
810
  CallNonClosureLabel = hipe_rtl:mk_new_label(),
 
811
  BadFunLabName = hipe_rtl:label_name(NonClosureLabel),
 
812
  BadFunCode =
 
813
    [NonClosureLabel,
 
814
     hipe_rtl:mk_call([NAddressReg],
 
815
                      'nonclosure_address',
 
816
                      [Fun, hipe_rtl:mk_imm(length(Args))],
 
817
                      hipe_rtl:label_name(CallNonClosureLabel),
 
818
                      Fail,
 
819
                      not_remote),
 
820
     CallNonClosureLabel,
 
821
     case Continuation of
 
822
       [] ->
 
823
         hipe_rtl:mk_enter(NAddressReg, Args, not_remote);
 
824
       _ ->
 
825
         hipe_rtl:mk_call(Dst, NAddressReg, Args, Continuation, Fail, not_remote)
 
826
     end],
 
827
 
 
828
  {BadArityLabName, BadArityCode} = gen_fail_code(Fail, {badarity, Fun}),
664
829
 
665
830
  CheckGetCode = 
666
 
    hipe_tagscheme:if_fun_get_arity_and_address(ArityReg,
667
 
                                                NAddressReg, Fun, 
668
 
                                                hipe_rtl:label_name(BadFunLab),
 
831
    hipe_tagscheme:if_fun_get_arity_and_address(ArityReg, NAddressReg,
 
832
                                                Fun, BadFunLabName,
669
833
                                                0.9),
670
 
  CheckArityCode = check_arity(ArityReg, length(Args), 
671
 
                               hipe_rtl:label_name(BadArityLab)),
672
 
 
673
 
  CallCode = 
 
834
  CheckArityCode = check_arity(ArityReg, length(RevArgs),
 
835
                               BadArityLabName),
 
836
  CallCode =
674
837
    case Continuation of
675
838
      [] -> %% This is a tailcall
676
 
        [hipe_rtl:mk_enter(NAddressReg, 
677
 
                           ArgsAndFun,
678
 
                           closure)]; 
 
839
        [hipe_rtl:mk_enter(NAddressReg, ArgsAndFun, not_remote)];
679
840
      _ -> %% Ordinary call
680
 
        [hipe_rtl:mk_call(Dst, NAddressReg, 
681
 
                          ArgsAndFun,
682
 
                          closure, 
683
 
                          Continuation, Fail)]
 
841
        [hipe_rtl:mk_call(Dst, NAddressReg, ArgsAndFun,
 
842
                          Continuation, Fail, not_remote)]
684
843
    end,
685
 
  [CheckGetCode,CheckArityCode, CallCode, FailCode].
686
 
 
 
844
  [CheckGetCode, CheckArityCode, CallCode, BadFunCode, BadArityCode].
687
845
 
688
846
check_arity(ArityReg, Arity, BadArityLab) ->
689
847
  TrueLab1 = hipe_rtl:mk_new_label(),
690
 
  _ArityCheckCode = 
691
 
    [hipe_rtl:mk_branch(ArityReg, eq, hipe_rtl:mk_imm(Arity),  
692
 
                        hipe_rtl:label_name(TrueLab1), BadArityLab,
693
 
                        0.9),
694
 
     TrueLab1].
695
 
 
696
 
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
697
 
 
698
 
 
699
 
 
 
848
  [hipe_rtl:mk_branch(ArityReg, eq, hipe_rtl:mk_imm(Arity),  
 
849
                      hipe_rtl:label_name(TrueLab1), BadArityLab, 0.9),
 
850
   TrueLab1].
700
851
 
701
852
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
702
853
%%
703
854
%% apply
704
 
%% NYI.
705
 
%%
706
 
 
707
 
%%gen_apply(Dst, Args, Cont, Fail, ExitInfo) ->
708
 
%%  Lab1 = hipe_rtl:mk_new_label(),
709
 
%%  Lab2 = hipe_rtl:mk_new_label(),
710
 
%%  CallEmuLab = hipe_rtl:mk_new_label(),
711
 
%%  CallDirectLab = hipe_rtl:mk_new_label(),
712
 
%%  ArityR = hipe_rtl:mk_new_reg(), 
713
 
%%  MFAReg =  hipe_rtl:mk_new_reg(), 
714
 
%%  AtomNoReg =  hipe_rtl:mk_new_reg(), 
715
 
%%  RequestReg =  hipe_rtl:mk_new_reg(), 
716
 
%%  AddressReg =  hipe_rtl:mk_new_reg(), 
717
 
 
718
 
%%  [M,F,AppArgs] = Args,
719
 
 
720
 
%%  [hipe_rtl:mk_call(ArityR, {erlang,length,1} , [AppArgs], c,  
721
 
%%                  hipe_rtl:label_name(Lab1), Fail),
722
 
%%   Lab1,
723
 
%%   hipe_rtl:mk_move(AtomNoReg, hipe_rtl:mk_imm(native_address))] ++
724
 
%%   gen_mk_tuple(MFAReg, [M,F,ArityR], []) ++
725
 
%%   gen_mk_tuple(RequestReg, [MFAReg,AtomNoReg], []) ++
726
 
%%    [
727
 
%%     hipe_rtl:mk_call(AddressReg, 
728
 
%%                    {hipe_bifs,get_funinfo,1} , [RequestReg], c,  
729
 
%%                    hipe_rtl:label_name(Lab2), Fail),
730
 
%%     Lab2,
731
 
%%     hipe_rtl:mk_branch(AddressReg, eq, 
732
 
%%                      hipe_rtl:mk_imm(hipe_tagscheme:mk_nil()), 
733
 
%%                       hipe_rtl:label_name(CallEmuLab), 
734
 
%%                      hipe_rtl:label_name(CallDirectLab), 0.01),
735
 
%%     CallEmuLab,
736
 
%%     generic_primop(Dst, {hipe_internal, apply, 3}, 
737
 
%%                         Args, Cont, Fail, ExitInfo),
738
 
%%     CallDirectLab,
739
 
%%     hipe_rtl:mk_call(Dst, AddressReg, 
740
 
%%                        AppArgs,
741
 
%%                        closure, 
742
 
%%                        Cont, 
743
 
%%                    Fail)].
744
 
 
 
855
%%
 
856
%% The tail call case is not handled here.
 
857
 
 
858
gen_apply(Dst, Args=[_M,_F,_AppArgs], Cont, Fail) ->
 
859
  %% Dst can be [Res] or [].
 
860
  [hipe_rtl:mk_call(Dst, hipe_apply, Args, Cont, Fail, not_remote)].
 
861
 
 
862
gen_enter_apply(Args=[_M,_F,_AppArgs]) ->
 
863
  %% 'apply' in tail-call context
 
864
  [hipe_rtl:mk_enter(hipe_apply, Args, not_remote)].
 
865
 
 
866
%%
 
867
%% apply_N
 
868
%% also handles tailcall case (Cont=[])
 
869
%%
 
870
 
 
871
gen_apply_N(Dst, Arity, [M,F|CallArgs], Cont, Fail) ->
 
872
  CallLabel = hipe_rtl:mk_new_label(),
 
873
  CodeAddress = hipe_rtl:mk_new_reg(),
 
874
  [hipe_rtl:mk_call([CodeAddress], find_na_or_make_stub,
 
875
                    [M,F,hipe_rtl:mk_imm(hipe_tagscheme:mk_fixnum(Arity))],
 
876
                    hipe_rtl:label_name(CallLabel),
 
877
                    Fail, not_remote),
 
878
   CallLabel,
 
879
   case Cont of
 
880
     [] ->      % tailcall
 
881
       hipe_rtl:mk_enter(CodeAddress, CallArgs, not_remote);
 
882
     _ ->       % recursive call
 
883
       hipe_rtl:mk_call(Dst, CodeAddress, CallArgs, Cont, Fail, not_remote)
 
884
   end].
745
885
 
746
886
 
747
887
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
749
889
%% mkTuple
750
890
%%
751
891
 
752
 
gen_mk_tuple(Dst, Elements, Options) ->
 
892
gen_mk_tuple(Dst, Elements) ->
753
893
  {GetHPInsn, HP, PutHPInsn} = hipe_rtl_arch:heap_pointer(),
754
894
  Arity = length(Elements),
755
 
 
756
 
  Code = [
757
 
          GetHPInsn,
758
 
          gen_tuple_header(HP, Arity),
759
 
          set_tuple_elements(HP, 4, Elements, []),
760
 
          hipe_tagscheme:tag_tuple(Dst, HP),
761
 
          hipe_rtl:mk_alu(HP, HP, add, hipe_rtl:mk_imm((Arity+1)*4)),
762
 
          PutHPInsn],
763
 
  case ?AddGC(Options) of
764
 
    true -> [hipe_rtl:mk_gctest(Arity + 1)|Code];
765
 
    false -> Code
766
 
  end.
767
 
 
768
 
set_tuple_elements(HP, Offset, [Element|Elements], Stores) ->
 
895
  WordSize = hipe_rtl_arch:word_size(),
 
896
  HeapNeed = (Arity+1)*WordSize,
 
897
  [GetHPInsn,
 
898
   gen_tuple_header(HP, Arity),
 
899
   set_tuple_elements(HP, WordSize, WordSize, Elements, []),
 
900
   hipe_tagscheme:tag_tuple(Dst, HP),
 
901
   hipe_rtl:mk_alu(HP, HP, add, hipe_rtl:mk_imm(HeapNeed)),
 
902
   PutHPInsn].
 
903
 
 
904
set_tuple_elements(HP, Offset, WordSize, [Element|Elements], Stores) ->
769
905
  Store = hipe_rtl:mk_store(HP, hipe_rtl:mk_imm(Offset), Element),
770
 
  set_tuple_elements(HP, Offset + 4, Elements, [Store | Stores]);
771
 
set_tuple_elements(_, _, [], Stores) ->
 
906
  set_tuple_elements(HP, Offset+WordSize, WordSize, Elements, [Store|Stores]);
 
907
set_tuple_elements(_, _, _, [], Stores) ->
772
908
  lists:reverse(Stores).
773
909
 
774
910
%%
775
 
%% Reduction test
 
911
%% @doc Generate RTL code for the reduction test.
776
912
%%
777
913
gen_redtest(Amount) ->
778
 
  Reds = hipe_rtl:mk_reg(hipe_rtl_arch:fcalls_reg()),
 
914
  {GetFCallsInsn, FCalls, PutFCallsInsn} = hipe_rtl_arch:fcalls(),
779
915
  SuspendLabel = hipe_rtl:mk_new_label(),
780
916
  StayLabel = hipe_rtl:mk_new_label(),
781
 
  [hipe_rtl:mk_alub(Reds, Reds, 'sub', hipe_rtl:mk_imm(Amount), 'lt',
 
917
  ContinueLabel = hipe_rtl:mk_new_label(),
 
918
  [GetFCallsInsn,
 
919
   hipe_rtl:mk_alub(FCalls, FCalls, 'sub', hipe_rtl:mk_imm(Amount), 'lt',
782
920
                    hipe_rtl:label_name(SuspendLabel),
783
921
                    hipe_rtl:label_name(StayLabel), 0.01),
784
922
   SuspendLabel,
785
 
   hipe_rtl:mk_call([], suspend_0, [], c, hipe_rtl:label_name(StayLabel), []),
786
 
   StayLabel].
 
923
   %% The suspend path should not execute PutFCallsInsn.
 
924
   hipe_rtl:mk_call([], suspend_0, [], hipe_rtl:label_name(ContinueLabel), [], not_remote),
 
925
   StayLabel,
 
926
   PutFCallsInsn,
 
927
   ContinueLabel].
 
928
 
 
929
gen_self(Dst, Cont) ->
 
930
  case Dst of
 
931
    [] -> %% The result is not used.
 
932
      [hipe_rtl:mk_goto(Cont)];
 
933
    [Dst1] ->
 
934
      [load_p_field(Dst1, ?P_ID),
 
935
       hipe_rtl:mk_goto(Cont)]
 
936
  end.
787
937
 
788
938
%%
789
939
%% Generate unsafe head
798
948
%%
799
949
%% element
800
950
%%
801
 
gen_element_2(Dst, Fail, Index, Tuple, Cont, _Annot, 
802
 
              ExitInfo, TupleInfo, IndexInfo) ->
803
 
  FailLbl = hipe_rtl:mk_new_label(),
804
 
  FailCode = hipe_rtl_exceptions:gen_fail_code(Fail, Dst, badarg, ExitInfo),
805
 
  [hipe_tagscheme:element(Dst, Index, Tuple, FailLbl, TupleInfo, IndexInfo),
 
951
gen_element(Dst, Args, IsGuard, Cont, Fail) ->
 
952
  Dst1 =
 
953
    case Dst of
 
954
      [] -> %% The result is not used.
 
955
        hipe_rtl:mk_new_var();
 
956
      [Dst0] -> Dst0
 
957
    end,
 
958
  [Index, Tuple] = Args,
 
959
  gen_element_1(Dst1, Index, Tuple, IsGuard, Cont, Fail, [], []).
 
960
 
 
961
gen_element_1(Dst, Index, Tuple, IsGuard, Cont, Fail, TupleInfo,
 
962
              IndexInfo) ->
 
963
  {FailLblName, FailCode} = gen_fail_code(Fail, badarg, IsGuard),
 
964
  [hipe_tagscheme:element(Dst, Index, Tuple, FailLblName, TupleInfo, IndexInfo),
806
965
   hipe_rtl:mk_goto(Cont),
807
 
   FailLbl,
808
966
   FailCode].
809
967
 
810
968
%%
814
972
  case hipe_rtl:is_imm(Index) of
815
973
    true -> hipe_tagscheme:unsafe_constant_element(Dst, Index, Tuple);
816
974
    false -> ?EXIT({illegal_index_to_unsafe_element,Index})
817
 
               end.
 
975
  end.
818
976
 
819
977
gen_unsafe_update_element(Tuple, Index, Value) ->
820
978
  case hipe_rtl:is_imm(Index) of
821
979
    true -> 
822
980
      hipe_tagscheme:unsafe_update_element(Tuple, Index, Value);
823
 
    false -> ?EXIT({illegal_index_to_unsafe_update_element,Index})
824
 
               end.
 
981
    false ->
 
982
      ?EXIT({illegal_index_to_unsafe_update_element,Index})
 
983
  end.
825
984
 
826
985
 
827
986
gen_closure_element(Dst, Index, Closure) ->
828
987
  hipe_tagscheme:unsafe_closure_element(Dst, Index, Closure).
829
988
 
830
989
%%
831
 
%% Generate code that writes a tuple header
 
990
%% @doc Generate RTL code that writes a tuple header.
832
991
%%
833
992
gen_tuple_header(Ptr, Arity) ->
834
993
  Header = hipe_tagscheme:mk_arityval(Arity),
835
994
  hipe_rtl:mk_store(Ptr, hipe_rtl:mk_imm(0), hipe_rtl:mk_imm(Header)).
836
995
 
837
 
 
838
 
%% ____________________________________________________________________
 
996
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
997
%%%
 
998
%%% Receives
 
999
 
 
1000
gen_check_get_msg(Dsts, GotoCont, Fail) ->
 
1001
  case ?ERTS_IS_SMP of
 
1002
    0 -> gen_check_get_msg_notsmp(Dsts, GotoCont, Fail);
 
1003
    1 -> gen_check_get_msg_smp(Dsts, GotoCont, Fail)
 
1004
  end.
 
1005
 
 
1006
gen_clear_timeout([], GotoCont) ->
 
1007
  case ?ERTS_IS_SMP of
 
1008
    0 -> gen_clear_timeout_notsmp(GotoCont);
 
1009
    1 -> gen_clear_timeout_smp(GotoCont)
 
1010
  end.
 
1011
 
 
1012
%%% check_get_msg is:
 
1013
%%%     if (!PEEK_MESSAGE(p)) goto Fail;
 
1014
%%%     Dst = ERL_MESSAGE_TERM(PEEK_MESSAGE(p));
 
1015
%%% i.e.,
 
1016
%%%     ErlMessage **save = p->msg.save;
 
1017
%%%     ErlMessage *msg = *save;
 
1018
%%%     if (!msg) goto Fail;
 
1019
%%%     Dst = msg->m[0];
 
1020
gen_check_get_msg_notsmp(Dsts, GotoCont, Fail) ->
 
1021
  Save = hipe_rtl:mk_new_reg(),
 
1022
  Msg = hipe_rtl:mk_new_reg(),
 
1023
  TrueLbl = hipe_rtl:mk_new_label(),
 
1024
  [load_p_field(Save, ?P_MSG_SAVE),
 
1025
   load_struct_field(Msg, Save, 0),
 
1026
   hipe_rtl:mk_branch(Msg, eq, hipe_rtl:mk_imm(0), Fail,
 
1027
                      hipe_rtl:label_name(TrueLbl), 0.1),
 
1028
   TrueLbl |
 
1029
   case Dsts of
 
1030
     [Dst] ->
 
1031
       [load_struct_field(Dst, Msg, ?MSG_MESSAGE),
 
1032
        GotoCont];
 
1033
     [] -> % receive which throws away the message
 
1034
       [GotoCont]
 
1035
   end].
 
1036
 
 
1037
%%% next_msg is:
 
1038
%%%     SAVE_MESSAGE(p);
 
1039
%%% i.e.,
 
1040
%%%     ErlMessage **save = p->msg.save;
 
1041
%%%     ErlMessage *msg = *save;
 
1042
%%%     ErlMessage **next = &msg->next;
 
1043
%%%     p->msg.save = next;
 
1044
gen_next_msg([], GotoCont) ->
 
1045
  Save = hipe_rtl:mk_new_reg(),
 
1046
  Msg = hipe_rtl:mk_new_reg(),
 
1047
  Rest1 = [GotoCont],
 
1048
  %%
 
1049
  Rest2 =
 
1050
    case ?MSG_NEXT of
 
1051
      0 ->
 
1052
        %% offsetof(ErlMessage,next) is normally 0, so "&msg->next"
 
1053
        %% becomes an add with 0. Unfortunately RTL doesn't optimise
 
1054
        %% that away; hence this special case.
 
1055
        [store_p_field(Msg, ?P_MSG_SAVE) |
 
1056
         Rest1];
 
1057
      _ ->
 
1058
        Next = hipe_rtl:mk_new_reg(),
 
1059
        [hipe_rtl:mk_alu(Next, Msg, 'add', hipe_rtl:mk_imm(?MSG_NEXT)),
 
1060
         store_p_field(Next, ?P_MSG_SAVE) |
 
1061
         Rest1]
 
1062
    end,
 
1063
  %%
 
1064
  [load_p_field(Save, ?P_MSG_SAVE),
 
1065
   load_struct_field(Msg, Save, 0) |
 
1066
   Rest2].
 
1067
 
 
1068
%%% clear_timeout is:
 
1069
%%%     p->flags &= ~F_TIMO; JOIN_MESSAGE(p);
 
1070
%%% i.e.,
 
1071
%%%     p->flags &= ~F_TIMO;
 
1072
%%%     p->msg.save = &p->msg.first;
 
1073
gen_clear_timeout_notsmp(GotoCont) ->
 
1074
  Flags1 = hipe_rtl:mk_new_reg(),
 
1075
  Flags2 = hipe_rtl:mk_new_reg_gcsafe(),
 
1076
  First = hipe_rtl:mk_new_reg_gcsafe(),
 
1077
  [load_p_field(Flags1, ?P_FLAGS),
 
1078
   hipe_rtl:mk_alu(Flags2, Flags1, 'and', hipe_rtl:mk_imm(bnot(?F_TIMO))),
 
1079
   store_p_field(Flags2, ?P_FLAGS),
 
1080
   hipe_rtl_arch:pcb_address(First, ?P_MSG_FIRST),
 
1081
   store_p_field(First, ?P_MSG_SAVE),
 
1082
   GotoCont].
 
1083
 
 
1084
gen_check_get_msg_smp(Dsts, GotoCont, Fail) ->
 
1085
  RetLbl = hipe_rtl:mk_new_label(),
 
1086
  TrueLbl = hipe_rtl:mk_new_label(),
 
1087
  Tmp = hipe_rtl:mk_new_reg(),
 
1088
  TheNonValue = hipe_rtl:mk_imm(hipe_tagscheme:mk_non_value()),
 
1089
  [hipe_rtl_arch:call_bif([Tmp], check_get_msg, [],
 
1090
                          hipe_rtl:label_name(RetLbl), []),
 
1091
   RetLbl,
 
1092
   hipe_rtl:mk_branch(Tmp, eq, TheNonValue, Fail,
 
1093
                      hipe_rtl:label_name(TrueLbl), 0.1),
 
1094
   TrueLbl |
 
1095
   case Dsts of
 
1096
     [Dst] ->
 
1097
       [hipe_rtl:mk_move(Dst, Tmp),
 
1098
        GotoCont];
 
1099
     [] -> % receive which throws away the message
 
1100
       [GotoCont]
 
1101
   end].
 
1102
 
 
1103
gen_clear_timeout_smp(GotoCont) ->
 
1104
  RetLbl = hipe_rtl:mk_new_label(),
 
1105
  [hipe_rtl_arch:call_bif([], clear_timeout, [],
 
1106
                          hipe_rtl:label_name(RetLbl), []),
 
1107
   RetLbl,
 
1108
   GotoCont].
 
1109
 
 
1110
gen_select_msg([], Cont) ->
 
1111
  [hipe_rtl_arch:call_bif([], select_msg, [], Cont, [])].
 
1112
 
 
1113
gen_suspend_msg([], Cont) ->
 
1114
  [hipe_rtl:mk_call([], suspend_msg, [], Cont, [], not_remote)].
 
1115
 
 
1116
%% --------------------------------------------------------------------
839
1117
%%
840
1118
%% Floating point handling 
841
1119
%%
842
1120
 
843
1121
gen_fclearerror() ->
844
 
  Addr = hipe_rtl:mk_new_reg(),
845
 
  [hipe_rtl:mk_load_address(Addr, erl_fp_exception, c_const),
846
 
   hipe_rtl:mk_store(Addr, hipe_rtl:mk_imm(0), hipe_rtl:mk_imm(0))].
 
1122
  case ?P_FP_EXCEPTION of
 
1123
    [] ->
 
1124
      [];
 
1125
    Offset ->
 
1126
      [hipe_rtl_arch:pcb_store(Offset, hipe_rtl:mk_imm(0), int32)]
 
1127
  end.
847
1128
 
848
 
gen_fcheckerror(ContLbl, FailLbl, ExitInfo)->
 
1129
gen_fcheckerror(ContLbl, FailLbl)->
849
1130
  Tmp = hipe_rtl:mk_new_reg(),
850
1131
  TmpFailLbl0 = hipe_rtl:mk_new_label(),
851
 
  TmpFailLbl1 = hipe_rtl:mk_new_label(),
852
 
  Result = hipe_rtl:mk_new_var(),
853
 
 
854
 
  Addr = hipe_rtl:mk_new_reg(),
855
 
 
856
 
  FailCode = fp_fail_code(TmpFailLbl0, TmpFailLbl1, 
857
 
                          FailLbl, Result, ExitInfo),
858
 
  ExceptionAtom = 
859
 
    case get(hipe_target_arch) of
860
 
      x86 -> erl_fp_check_exception;
861
 
      ultrasparc -> erl_fp_exception
862
 
    end,
863
 
  
864
 
  [hipe_rtl:mk_load_address(Addr, ExceptionAtom, c_const),
865
 
   hipe_rtl:mk_load(Tmp, Addr, hipe_rtl:mk_imm(0)),
866
 
   hipe_rtl:mk_branch(Tmp, eq, hipe_rtl:mk_imm(0), 
867
 
                      ContLbl, hipe_rtl:label_name(TmpFailLbl0))]++
 
1132
  FailCode = fp_fail_code(TmpFailLbl0, FailLbl),
 
1133
  hipe_rtl_arch:fwait() ++
 
1134
    case ?P_FP_EXCEPTION of
 
1135
      [] ->
 
1136
        [];
 
1137
      Offset ->
 
1138
        [hipe_rtl_arch:pcb_load(Tmp, Offset, int32)]
 
1139
    end ++
 
1140
    [hipe_rtl:mk_branch(Tmp, eq, hipe_rtl:mk_imm(0), 
 
1141
                       ContLbl, hipe_rtl:label_name(TmpFailLbl0), 0.9)] ++
868
1142
    FailCode.
869
1143
 
870
 
gen_conv_to_float(Dst, [Src], ContLbl, FailLbl, ExitInfo) ->
 
1144
gen_conv_to_float(Dst, [Src], ContLbl, FailLbl) ->
871
1145
  case hipe_rtl:is_var(Src) of
872
1146
    true ->
873
1147
      Tmp = hipe_rtl:mk_new_var(),
874
 
      TmpReg = hipe_rtl:mk_new_reg(),
 
1148
      TmpReg = hipe_rtl:mk_new_reg_gcsafe(),
875
1149
      TrueFixNum = hipe_rtl:mk_new_label(),
876
1150
      ContFixNum = hipe_rtl:mk_new_label(),
877
1151
      TrueFp = hipe_rtl:mk_new_label(),
878
1152
      ContFp = hipe_rtl:mk_new_label(),
879
1153
      ContBigNum = hipe_rtl:mk_new_label(),
880
 
      TestFixNum = hipe_tagscheme:test_fixnum(Src, hipe_rtl:label_name(TrueFixNum),
881
 
                                              hipe_rtl:label_name(ContFixNum), 0.5),
 
1154
      TestFixNum = hipe_tagscheme:test_fixnum(Src,
 
1155
                                              hipe_rtl:label_name(TrueFixNum),
 
1156
                                              hipe_rtl:label_name(ContFixNum),
 
1157
                                              0.5),
882
1158
      TestFp = hipe_tagscheme:test_flonum(Src, hipe_rtl:label_name(TrueFp),
883
1159
                                          hipe_rtl:label_name(ContFp), 0.5),
884
1160
      GotoCont = hipe_rtl:mk_goto(ContLbl),
885
1161
      TmpFailLbl0 = hipe_rtl:mk_new_label(),
886
 
      TmpFailLbl1 = hipe_rtl:mk_new_label(),
887
 
      Result = hipe_rtl:mk_new_var(),
888
 
      FailCode = fp_fail_code(TmpFailLbl0, TmpFailLbl1, 
889
 
                              FailLbl, Result, ExitInfo),
 
1162
      FailCode = fp_fail_code(TmpFailLbl0, FailLbl),
890
1163
 
891
1164
      TestFixNum ++
892
1165
        [TrueFixNum, 
899
1172
         hipe_tagscheme:unsafe_untag_float(Dst, Src), 
900
1173
         GotoCont, 
901
1174
         ContFp] ++
902
 
        [hipe_rtl:mk_call([Tmp],conv_big_to_float,[Src], c,
 
1175
        [hipe_rtl:mk_call([Tmp],conv_big_to_float,[Src],
903
1176
                          hipe_rtl:label_name(ContBigNum),
904
 
                          hipe_rtl:label_name(TmpFailLbl0))]++
 
1177
                          hipe_rtl:label_name(TmpFailLbl0), not_remote)]++
905
1178
        FailCode ++
906
1179
        [ContBigNum,
907
1180
         hipe_tagscheme:unsafe_untag_float(Dst, Tmp)];
908
1181
    _ ->
909
1182
      %% This must be an attempt to convert an illegal term.
910
 
      Result = hipe_rtl:mk_new_var(),
911
 
      [hipe_rtl_exceptions:gen_fail_code(FailLbl, Result, badarith, ExitInfo)]
912
 
  end.
913
 
 
914
 
fp_fail_code(TmpFailLbl0, TmpFailLbl1, FailLbl, Result, ExitInfo)->
915
 
  case get(hipe_target_arch) of
916
 
    x86 ->
917
 
      [TmpFailLbl0,
918
 
       hipe_rtl:mk_call([], handle_fp_exception, [], c,
919
 
                        hipe_rtl:label_name(TmpFailLbl1), []),
920
 
       TmpFailLbl1,
921
 
       hipe_rtl_exceptions:gen_fail_code(FailLbl, Result, 
922
 
                                         badarith, ExitInfo)];
923
 
    ultrasparc ->
924
 
      [TmpFailLbl0,
925
 
       hipe_rtl_exceptions:gen_fail_code
926
 
       (FailLbl, Result, badarith, ExitInfo)]
927
 
  end.
928
 
  
929
 
%% ____________________________________________________________________
930
 
%%
931
 
%% Type handling.
932
 
%%
933
 
 
934
 
type('+', Args)->
935
 
  erl_bif_types:type(erlang, '+', 2, Args);
936
 
type('-', Args)->
937
 
  erl_bif_types:type(erlang, '-', 2, Args);
938
 
type(cons, [HeadType, TailType])->
939
 
  erl_types:t_cons(HeadType, TailType);
940
 
type(unsafe_tl, [Type]) ->
941
 
  case erl_types:t_is_cons(Type) of
942
 
    true -> erl_types:t_cons_tl(Type);
943
 
    _ -> erl_types:t_undefined()
944
 
  end;
945
 
type(unsafe_hd, [Type]) ->
946
 
  case erl_types:t_is_cons(Type) of
947
 
    true -> erl_types:t_cons_hd(Type);
948
 
    _ -> erl_types:t_undefined()
949
 
  end;
950
 
type(mktuple, TypeList) ->
951
 
  erl_types:t_tuple(TypeList);
952
 
type(unsafe_element, [IndexType, TupleType]) ->
953
 
  case erl_types:t_number_vals(IndexType) of
954
 
    [N] when is_integer(N)->
955
 
      type({unsafe_element, N}, TupleType);
956
 
    _ ->
957
 
      case erl_types:t_is_tuple(TupleType) of
958
 
        false ->
959
 
          erl_types:t_any();
960
 
        _ ->
961
 
          case erl_types:t_tuple_args(TupleType) of
962
 
            [H|T] = List when is_list(List) ->
963
 
              case lists:all(fun(X)->X=:=H end, T) of
964
 
                true -> H;
965
 
                _ -> erl_types:t_any()
966
 
              end;
967
 
            _ ->
968
 
              erl_types:t_any()
969
 
          end
970
 
      end
971
 
  end;
972
 
type({unsafe_element, N}, [Type]) ->
973
 
  case erl_types:t_is_tuple(Type) of
974
 
    false ->
975
 
      erl_types:t_any();  
976
 
    _ ->
977
 
      case erl_types:t_tuple_args(Type) of
978
 
        ArgTypes when is_list(ArgTypes) ->
979
 
          lists:nth(N, ArgTypes);
980
 
        T -> T
981
 
      end
982
 
  end;
983
 
type(unsafe_tag_float, _) ->
984
 
  erl_types:t_float();
985
 
type('bor', Args)->
986
 
  erl_bif_types:type(erlang, 'bor', 2, Args);
987
 
type('band', Args)->
988
 
  erl_bif_types:type(erlang, 'band', 2, Args);
989
 
type('bxor', Args)->
990
 
  erl_bif_types:type(erlang, 'bxor', 2, Args);
991
 
type('bnot', Args)->
992
 
  erl_bif_types:type(erlang, 'bnot', 2, Args);
993
 
type({hipe_bs_primop, {bs_get_integer, _, _}}, _) ->
994
 
  %%TODO: Here we could find out if this is a fixnum.
995
 
  erl_types:t_integer();
996
 
type({hipe_bs_primop, {bs_get_float, _, _}}, _) ->
997
 
  erl_types:t_float();
998
 
type({hipe_bs_primop, {bs_get_binary, _, _}}, _) ->
999
 
  erl_types:t_binary();
1000
 
type({hipe_bs_primop, {bs_get_binary_all, _}}, _) ->
1001
 
  erl_types:t_binary();
1002
 
type({hipe_bs_primop, bs_final}, _) ->
1003
 
  erl_types:t_binary();
1004
 
type(_Op, _) ->
1005
 
  %%io:format("Don't have any information for ~w\n", [Op]),
1006
 
  erl_types:t_any().
 
1183
      [gen_fail_code(FailLbl, badarith)]
 
1184
  end.
1007
1185