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

« back to all changes in this revision

Viewing changes to lib/hipe/cerl/erl_bif_types.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2010-03-09 17:34:57 UTC
  • mfrom: (10.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20100309173457-4yd6hlcb2osfhx31
Tags: 1:13.b.4-dfsg-3
Manpages in section 1 are needed even if only arch-dependent packages are
built. So, re-enabled them.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%% -*- erlang-indent-level: 2 -*-
2
2
%%
3
3
%% %CopyrightBegin%
4
 
%% 
5
 
%% Copyright Ericsson AB 2003-2009. All Rights Reserved.
6
 
%% 
 
4
%%
 
5
%% Copyright Ericsson AB 2003-2010. All Rights Reserved.
 
6
%%
7
7
%% The contents of this file are subject to the Erlang Public License,
8
8
%% Version 1.1, (the "License"); you may not use this file except in
9
9
%% compliance with the License. You should have received a copy of the
10
10
%% Erlang Public License along with this software. If not, it can be
11
11
%% retrieved online at http://www.erlang.org/.
12
 
%% 
 
12
%%
13
13
%% Software distributed under the License is distributed on an "AS IS"
14
14
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
15
15
%% the License for the specific language governing rights and limitations
16
16
%% under the License.
17
 
%% 
 
17
%%
18
18
%% %CopyrightEnd%
19
19
%%
20
20
%% =====================================================================
102
102
                    t_list_elements/1,
103
103
                    t_list_termination/1,
104
104
                    t_mfa/0,
 
105
                    t_module/0,
105
106
                    t_nil/0,
106
107
                    t_node/0,
107
108
                    t_none/0,
694
695
         fun (_) -> t_list(t_byte()) end);
695
696
type(erlang, binary_to_term, 1, Xs) ->
696
697
  strict(arg_types(erlang, binary_to_term, 1), Xs, fun (_) -> t_any() end);
 
698
type(erlang, binary_to_term, 2, Xs) ->
 
699
  strict(arg_types(erlang, binary_to_term, 2), Xs, fun (_) -> t_any() end);
697
700
type(erlang, bitsize, 1, Xs) -> % XXX: TAKE OUT
698
701
  type(erlang, bit_size, 1, Xs);
699
702
type(erlang, bit_size, 1, Xs) ->
710
713
type(erlang, byte_size, 1, Xs) ->
711
714
  strict(arg_types(erlang, byte_size, 1), Xs,
712
715
         fun (_) -> t_non_neg_integer() end);
 
716
type(erlang, call_on_load_function, 1, Xs) ->
 
717
  %% Internal BIF used by on_load.
 
718
  strict(arg_types(erlang, call_on_load_function, 1), Xs,
 
719
         fun (_) -> t_any() end);
713
720
type(erlang, cancel_timer, 1, Xs) ->
714
721
  strict(arg_types(erlang, cancel_timer, 1), Xs,
715
722
         fun (_) -> t_sup(t_integer(), t_atom('false')) end);
773
780
type(erlang, erase, 0, _) -> t_any();
774
781
type(erlang, erase, 1, _) -> t_any();
775
782
type(erlang, external_size, 1, _) -> t_integer();
 
783
type(erlang, finish_after_on_load, 2, Xs) ->
 
784
  %% Internal BIF used by on_load.
 
785
  strict(arg_types(erlang, finish_after_on_load, 2), Xs,
 
786
         fun (_) -> t_atom('true') end);
776
787
type(erlang, float, 1, Xs) ->
777
788
  strict(arg_types(erlang, float, 1), Xs, fun (_) -> t_float() end);
778
789
type(erlang, float_to_list, 1, Xs) ->
1760
1771
         fun (_) -> t_sup([t_atom('false'),
1761
1772
                           t_atom('undef'),
1762
1773
                           t_tuple([t_integer(), t_binary(), t_mfa()])]) end);
 
1774
type(erts_debug, dist_ext_to_term, 2, Xs) ->
 
1775
  strict(arg_types(erts_debug, dist_ext_to_term, 2), Xs,
 
1776
         fun (_) -> t_any() end);
1763
1777
type(erts_debug, flat_size, 1, Xs) ->
1764
1778
  strict(arg_types(erts_debug, flat_size, 1), Xs, fun (_) -> t_integer() end);
 
1779
type(erts_debug, lock_counters, 1, Xs) ->
 
1780
  strict(arg_types(erts_debug, lock_counters, 1), Xs,
 
1781
         fun ([Arg]) ->
 
1782
             case t_is_atom(Arg) of
 
1783
               true ->
 
1784
                 case t_atom_vals(Arg) of
 
1785
                   ['enabled'] -> t_boolean();
 
1786
                   ['info'] -> t_any();
 
1787
                   ['clear'] -> t_atom(ok);
 
1788
                   _ -> t_sup([t_boolean(), t_any(), t_atom('ok')])
 
1789
                 end;
 
1790
               false ->
 
1791
                 case t_is_tuple(Arg) of
 
1792
                   true -> t_boolean();
 
1793
                   false -> t_sup([t_boolean(), t_any(), t_atom('ok')])
 
1794
                 end
 
1795
             end
 
1796
         end);
1765
1797
type(erts_debug, same, 2, Xs) ->
1766
1798
  strict(arg_types(erts_debug, same, 2), Xs, fun (_) -> t_boolean() end);
1767
1799
%%-- ets ----------------------------------------------------------------------
2661
2693
type(os, getpid, 0, _) -> t_string();
2662
2694
type(os, putenv, 2, Xs) ->
2663
2695
  strict(arg_types(os, putenv, 2), Xs, fun (_) -> t_atom('true') end);
 
2696
type(os, timestamp, 0, _) ->
 
2697
  t_time();
2664
2698
%%-- re -----------------------------------------------------------------------
2665
2699
type(re, compile, 1, Xs) ->
2666
2700
  strict(arg_types(re, compile, 1), Xs,
3119
3153
            end,
3120
3154
          %% io:format("done arith ~p = ~p~n", [Op, {NewMin, NewMax}]),
3121
3155
          {ok, t_from_range(NewMin, NewMax)};
3122
 
        false ->  
3123
 
          AllVals =
3124
 
            case Op of
3125
 
              '+'    -> [X + Y    || X <- L1, Y <- L2];
3126
 
              '-'    -> [X - Y    || X <- L1, Y <- L2];
3127
 
              '*'    -> [X * Y    || X <- L1, Y <- L2];
3128
 
              'div'  -> [X div Y  || X <- L1, Y <- L2,Y =/= 0];
3129
 
              'rem'  -> [X rem Y  || X <- L1, Y <- L2,Y =/= 0];
3130
 
              'bsl'  -> [X bsl Y  || X <- L1, Y <- L2];
3131
 
              'bsr'  -> [X bsr Y  || X <- L1, Y <- L2];
3132
 
              'band' -> [X band Y || X <- L1, Y <- L2];
3133
 
              'bor'  -> [X bor Y  || X <- L1, Y <- L2];
3134
 
              'bxor' -> [X bxor Y || X <- L1, Y <- L2]
3135
 
            end,
3136
 
          {ok, t_integers(ordsets:from_list(AllVals))}
 
3156
        false ->
 
3157
          %% Some of these arithmetic operations might throw a system_limit
 
3158
          %% exception; for example, when trying to evaluate 1 bsl 100000000.
 
3159
          try case Op of
 
3160
                '+'    -> [X + Y    || X <- L1, Y <- L2];
 
3161
                '-'    -> [X - Y    || X <- L1, Y <- L2];
 
3162
                '*'    -> [X * Y    || X <- L1, Y <- L2];
 
3163
                'div'  -> [X div Y  || X <- L1, Y <- L2, Y =/= 0];
 
3164
                'rem'  -> [X rem Y  || X <- L1, Y <- L2, Y =/= 0];
 
3165
                'bsl'  -> [X bsl Y  || X <- L1, Y <- L2];
 
3166
                'bsr'  -> [X bsr Y  || X <- L1, Y <- L2];
 
3167
                'band' -> [X band Y || X <- L1, Y <- L2];
 
3168
                'bor'  -> [X bor Y  || X <- L1, Y <- L2];
 
3169
                'bxor' -> [X bxor Y || X <- L1, Y <- L2]
 
3170
              end of
 
3171
            AllVals ->
 
3172
              {ok, t_integers(ordsets:from_list(AllVals))}
 
3173
          catch
 
3174
            error:system_limit -> error
 
3175
          end
3137
3176
      end
3138
3177
  end.
3139
3178
 
3325
3364
arg_types(erlang, append_element, 2) ->
3326
3365
  [t_tuple(), t_any()];
3327
3366
arg_types(erlang, apply, 2) ->
3328
 
  [t_sup(t_tuple([t_sup(t_atom(),   % module name
3329
 
                        t_tuple()), % parameterized module          
 
3367
  [t_sup(t_tuple([t_module(),
3330
3368
                  t_atom()]),
3331
3369
         t_fun()),
3332
3370
   t_list()];
3346
3384
  [t_binary(), t_pos_integer(), t_pos_integer()]; % I want fixnum, but cannot
3347
3385
arg_types(erlang, binary_to_term, 1) ->
3348
3386
  [t_binary()];
 
3387
arg_types(erlang, binary_to_term, 2) ->
 
3388
  [t_binary(), t_list(t_atom('safe'))];
3349
3389
arg_types(erlang, bitsize, 1) ->        % XXX: TAKE OUT
3350
3390
  arg_types(erlang, bit_size, 1);
3351
3391
arg_types(erlang, bit_size, 1) ->
3358
3398
  [t_pos_fixnum()];
3359
3399
arg_types(erlang, byte_size, 1) ->
3360
3400
  [t_binary()];
 
3401
arg_types(erlang, call_on_load_function, 1) ->
 
3402
  [t_atom()];
3361
3403
arg_types(erlang, cancel_timer, 1) ->
3362
3404
  [t_reference()];
3363
3405
arg_types(erlang, check_process_code, 2) ->
3402
3444
  [t_sup(t_pid(), t_port()), t_any()];
3403
3445
arg_types(erlang, external_size, 1) ->
3404
3446
  [t_any()]; % takes any term as input
 
3447
arg_types(erlang, finish_after_on_load, 2) ->
 
3448
  [t_atom(), t_boolean()];
3405
3449
arg_types(erlang, float, 1) ->
3406
3450
  [t_number()];
3407
3451
arg_types(erlang, float_to_list, 1) ->
3853
3897
  [t_tuple([t_atom(), t_atom(), t_sup(t_integer(), t_atom('_'))]), t_boolean()];
3854
3898
arg_types(erts_debug, disassemble, 1) ->
3855
3899
  [t_sup(t_mfa(), t_integer())];
 
3900
arg_types(erts_debug, dist_ext_to_term, 2) ->
 
3901
  [t_tuple(), t_binary()];
3856
3902
arg_types(erts_debug, flat_size, 1) ->
3857
3903
  [t_any()];
 
3904
arg_types(erts_debug, lock_counters, 1) ->
 
3905
  [t_sup([t_atom(enabled),
 
3906
          t_atom(info),
 
3907
          t_atom(clear),
 
3908
          t_tuple([t_atom(copy_save), t_boolean()]),
 
3909
          t_tuple([t_atom(process_locks), t_boolean()])])];
3858
3910
arg_types(erts_debug, same, 2) ->
3859
3911
  [t_any(), t_any()];
3860
3912
%%------- ets -----------------------------------------------------------------
4277
4329
  [];
4278
4330
arg_types(os, putenv, 2) ->
4279
4331
  [t_string(), t_string()];
 
4332
arg_types(os, timestamp, 0) ->
 
4333
  [];
4280
4334
%%-- re -----------------------------------------------------------------------
4281
4335
arg_types(re, compile, 1) ->
4282
4336
  [t_iodata()];
4334
4388
structure_inspecting_args(erlang, is_port, 1) -> [1];
4335
4389
structure_inspecting_args(erlang, is_reference, 1) -> [1];
4336
4390
structure_inspecting_args(erlang, is_tuple, 1) -> [1];
 
4391
structure_inspecting_args(erlang, length, 1) -> [1];
4337
4392
%%structure_inspecting_args(erlang, setelement, 3) -> [2].
4338
4393
structure_inspecting_args(_, _, _) -> []. % XXX: assume no arg needs inspection
4339
4394
 
4462
4517
         t_atom('nofile'),
4463
4518
         t_atom('not_purged'),
4464
4519
         t_atom('native_code'),
 
4520
         t_atom('on_load'),
4465
4521
         t_atom('sticky_directory')]).  % only for the 'code' functions
4466
4522
 
4467
4523
t_code_loaded_fname_or_status() ->
4893
4949
         t_integers([0,1,2,4]),
4894
4950
         t_atom('asn1'), t_atom('cdr'), t_atom('sunrm'),
4895
4951
         t_atom('fcgi'), t_atom('tpkt'), t_atom('line'),
4896
 
         t_atom('http')]).      %% but t_atom('httph') is not needed
 
4952
         t_atom('http'),
 
4953
         t_atom('http_bin')]).  %% but t_atom('httph') is not needed
4897
4954
 
4898
4955
t_inet_posix_error() ->
4899
4956
  t_atom().  %% XXX: Very underspecified