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

« back to all changes in this revision

Viewing changes to lib/stdlib/src/erl_internal.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:
69
69
guard_bif(node,1) -> true;
70
70
guard_bif(is_atom, 1) -> true;
71
71
guard_bif(is_binary, 1) -> true;
 
72
guard_bif(is_boolean, 1) -> true;
72
73
guard_bif(is_constant, 1) -> true;
73
74
guard_bif(is_float, 1) -> true;
74
75
guard_bif(is_function, 1) -> true;
 
76
guard_bif(is_function, 2) -> true;
75
77
guard_bif(is_integer, 1) -> true;
76
78
guard_bif(is_list, 1) -> true;
77
79
guard_bif(is_number, 1) -> true;
80
82
guard_bif(is_reference, 1) -> true;
81
83
guard_bif(is_tuple, 1) -> true;
82
84
guard_bif(is_record, 2) -> true;
83
 
guard_bif(_, _) -> false.
 
85
guard_bif(is_record, 3) -> true;
 
86
guard_bif(Name, A) when is_atom(Name), is_integer(A) -> false.
84
87
 
85
88
%% -type type_test(Name, Arity) -> bool()
86
89
%%      when Name = atom(), Arity = integer().
94
97
%%  Erlang new-style type tests.
95
98
 
96
99
new_type_test(is_atom, 1) -> true;
 
100
new_type_test(is_boolean, 1) -> true;
97
101
new_type_test(is_binary, 1) -> true;
98
102
new_type_test(is_constant, 1) -> true;
99
103
new_type_test(is_float, 1) -> true;
100
104
new_type_test(is_function, 1) -> true;
 
105
new_type_test(is_function, 2) -> true;
101
106
new_type_test(is_integer, 1) -> true;
102
107
new_type_test(is_list, 1) -> true;
103
108
new_type_test(is_number, 1) -> true;
106
111
new_type_test(is_reference, 1) -> true;
107
112
new_type_test(is_tuple, 1) -> true;
108
113
new_type_test(is_record, 2) -> true;
109
 
new_type_test(_, _) -> false.
 
114
new_type_test(is_record, 3) -> true;
 
115
new_type_test(Name, A) when is_atom(Name), is_integer(A) -> false.
110
116
 
111
117
%% -type old_type_test(Name, Arity) -> bool()
112
118
%%      when Name = atom(), Arity = integer().
125
131
old_type_test(binary, 1) -> true;
126
132
old_type_test(record, 2) -> true;
127
133
old_type_test(function, 1) -> true;
128
 
old_type_test(_, _) -> false.
 
134
old_type_test(Name, A) when is_atom(Name), is_integer(A) -> false.
129
135
 
130
136
%% -type arith_op(Op, Arity) -> bool()
131
137
%%      when Op = atom(), Arity = integer().
144
150
arith_op('bxor', 2) -> true;
145
151
arith_op('bsl', 2) -> true;
146
152
arith_op('bsr', 2) -> true;
147
 
arith_op(_, _) -> false.
 
153
arith_op(Op, A) when is_atom(Op), is_integer(A) -> false.
148
154
 
149
155
%% -type bool_op(Op, Arity) -> bool()
150
156
%%      when Op = atom(), Arity = integer().
153
159
bool_op('and', 2) -> true;
154
160
bool_op('or', 2) -> true;
155
161
bool_op('xor', 2) -> true;
156
 
bool_op(_, _) -> false.
 
162
bool_op(Op, A) when is_atom(Op), is_integer(A) -> false.
157
163
 
158
164
%% -type comp_op(Op, Arity) -> bool()
159
165
%%      when Op = atom(), Arity = integer().
166
172
comp_op('>', 2) -> true;
167
173
comp_op('=:=', 2) -> true;
168
174
comp_op('=/=', 2) -> true;
169
 
comp_op(_, _) -> false.
 
175
comp_op(Op, A) when is_atom(Op), is_integer(A) -> false.
170
176
 
171
177
%% -type list_op(Op, Arity) -> bool()
172
178
%%      when Op = atom(), Arity = integer().
173
179
 
174
180
list_op('++', 2) -> true;
175
181
list_op('--', 2) -> true;
176
 
list_op(_, _) -> false.
 
182
list_op(Op, A) when is_atom(Op), is_integer(A) -> false.
177
183
 
178
184
%% -type send_op(Op, Arity) -> bool()
179
185
%%      when Op = atom(), Arity = integer().
180
186
 
181
187
send_op('!', 2) -> true;
182
 
send_op(_, _) -> false.
 
188
send_op(Op, A) when is_atom(Op), is_integer(A) -> false.
183
189
 
184
190
%% -type op_type(Op, Arity) -> arith | bool | comp | list | send
185
191
%%      when Op = atom(), Arity = integer().
215
221
op_type('!', 2) -> send.
216
222
 
217
223
bif(erlang, Name, Arity) -> bif(Name, Arity);
218
 
bif(_, _, _) -> false.
 
224
bif(M, F, A) when is_atom(M), is_atom(F), is_integer(A) -> false.
219
225
 
220
226
%% bif(Name, Arity) -> true|false
221
227
%%   Returns true if erlang:Name/Arity is an auto-imported BIF, false otherwise.
252
258
bif(halt, 1) -> true;
253
259
bif(hd, 1) -> true;
254
260
bif(integer_to_list, 1) -> true;
 
261
bif(iolist_size, 1) -> true;
 
262
bif(iolist_to_binary, 1) -> true;
255
263
bif(is_alive, 0) -> true;
256
264
bif(is_process_alive, 1) -> true;
257
265
bif(is_atom, 1) -> true;
 
266
bif(is_boolean, 1) -> true;
258
267
bif(is_binary, 1) -> true;
259
268
bif(is_constant, 1) -> true;
260
269
bif(is_float, 1) -> true;
261
270
bif(is_function, 1) -> true;
 
271
bif(is_function, 2) -> true;
262
272
bif(is_integer, 1) -> true;
263
273
bif(is_list, 1) -> true;
264
274
bif(is_number, 1) -> true;
267
277
bif(is_reference, 1) -> true;
268
278
bif(is_tuple, 1) -> true;
269
279
bif(is_record, 2) -> true;
 
280
bif(is_record, 3) -> true;
270
281
bif(length, 1) -> true;
271
282
bif(link, 1) -> true;
272
283
bif(list_to_atom, 1) -> true;
273
284
bif(list_to_binary, 1) -> true;
 
285
bif(list_to_existing_atom, 1) -> true;
274
286
bif(list_to_float, 1) -> true;
275
287
bif(list_to_integer, 1) -> true;
276
288
bif(list_to_pid, 1) -> true;
328
340
bif(unlink, 1) -> true;
329
341
bif(unregister, 1) -> true;
330
342
bif(whereis, 1) -> true;
331
 
bif(_, _) -> false.
 
343
bif(Name, A) when is_atom(Name), is_integer(A) -> false.
332
344
 
333
345
obsolete(Mod, Fun, Arity) ->
334
346
    %% Just in case.