~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to lib/stdlib/src/otp_internal.erl

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 1999-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 1999-2010. All Rights Reserved.
 
5
%%
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
8
8
%% compliance with the License. You should have received a copy of the
9
9
%% Erlang Public License along with this software. If not, it can be
10
10
%% retrieved online at http://www.erlang.org/.
11
 
%% 
 
11
%%
12
12
%% Software distributed under the License is distributed on an "AS IS"
13
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
%% the License for the specific language governing rights and limitations
15
15
%% under the License.
16
 
%% 
 
16
%%
17
17
%% %CopyrightEnd%
18
18
%%
19
19
-module(otp_internal).
236
236
obsolete_1(file, rawopen, 2) ->
237
237
    {removed, "deprecated (will be removed in R13B); use file:open/2 with the raw option"};
238
238
 
239
 
obsolete_1(httpd, start, 0)       -> {deprecated,{inets,start,[2,3]},"R14B"};
240
 
obsolete_1(httpd, start, 1)       -> {deprecated,{inets,start,[2,3]},"R14B"};
241
 
obsolete_1(httpd, start_link, 1)  -> {deprecated,{inets,start,[2,3]},"R14B"};
242
 
obsolete_1(httpd, start_child, 0) -> {deprecated,{inets,start,[2,3]},"R14B"};
243
 
obsolete_1(httpd, start_child, 1) -> {deprecated,{inets,start,[2,3]},"R14B"};
244
 
obsolete_1(httpd, stop, 0)        -> {deprecated,{inets,stop,2},"R14B"};
245
 
obsolete_1(httpd, stop, 1)        -> {deprecated,{inets,stop,2},"R14B"};
246
 
obsolete_1(httpd, stop, 2)        -> {deprecated,{inets,stop,2},"R14B"};
247
 
obsolete_1(httpd, stop_child, 0)  -> {deprecated,{inets,stop,2},"R14B"};
248
 
obsolete_1(httpd, stop_child, 1)  -> {deprecated,{inets,stop,2},"R14B"};
249
 
obsolete_1(httpd, stop_child, 2)  -> {deprecated,{inets,stop,2},"R14B"};
250
 
obsolete_1(httpd, restart, 0)     -> {deprecated,{httpd,reload_config,2},"R14B"};
251
 
obsolete_1(httpd, restart, 1)     -> {deprecated,{httpd,reload_config,2},"R14B"};
252
 
obsolete_1(httpd, restart, 2)     -> {deprecated,{httpd,reload_config,2},"R14B"};
253
 
obsolete_1(httpd, block, 0)       -> {deprecated,{httpd,reload_config,2},"R14B"};
254
 
obsolete_1(httpd, block, 1)       -> {deprecated,{httpd,reload_config,2},"R14B"};
255
 
obsolete_1(httpd, block, 2)       -> {deprecated,{httpd,reload_config,2},"R14B"};
256
 
obsolete_1(httpd, block, 3)       -> {deprecated,{httpd,reload_config,2},"R14B"};
257
 
obsolete_1(httpd, block, 4)       -> {deprecated,{httpd,reload_config,2},"R14B"};
258
 
obsolete_1(httpd, unblock, 0)     -> {deprecated,{httpd,reload_config,2},"R14B"};
259
 
obsolete_1(httpd, unblock, 1)     -> {deprecated,{httpd,reload_config,2},"R14B"};
260
 
obsolete_1(httpd, unblock, 2)     -> {deprecated,{httpd,reload_config,2},"R14B"};
 
239
obsolete_1(http, request, 1)          -> {deprecated,{httpc,request,1},"R15B"};
 
240
obsolete_1(http, request, 2)          -> {deprecated,{httpc,request,2},"R15B"};
 
241
obsolete_1(http, request, 4)          -> {deprecated,{httpc,request,4},"R15B"};
 
242
obsolete_1(http, request, 5)          -> {deprecated,{httpc,request,5},"R15B"};
 
243
obsolete_1(http, cancel_request, 1)   -> {deprecated,{httpc,cancel_request,1},"R15B"};
 
244
obsolete_1(http, cancel_request, 2)   -> {deprecated,{httpc,cancel_request,2},"R15B"};
 
245
obsolete_1(http, set_option, 2)       -> {deprecated,{httpc,set_option,2},"R15B"};
 
246
obsolete_1(http, set_option, 3)       -> {deprecated,{httpc,set_option,3},"R15B"};
 
247
obsolete_1(http, set_options, 1)      -> {deprecated,{httpc,set_options,1},"R15B"};
 
248
obsolete_1(http, set_options, 2)      -> {deprecated,{httpc,set_options,2},"R15B"};
 
249
obsolete_1(http, verify_cookies, 2)   -> {deprecated,{httpc,verify_cookies,2},"R15B"};
 
250
obsolete_1(http, verify_cookies, 3)   -> {deprecated,{httpc,verify_cookies,3},"R15B"};
 
251
obsolete_1(http, cookie_header, 1)    -> {deprecated,{httpc,cookie_header,1},"R15B"};
 
252
obsolete_1(http, cookie_header, 2)    -> {deprecated,{httpc,cookie_header,2},"R15B"};
 
253
obsolete_1(http, stream_next, 1)      -> {deprecated,{httpc,stream_next,1},"R15B"};
 
254
obsolete_1(http, default_profile, 0)  -> {deprecated,{httpc,default_profile,0},"R15B"};
 
255
 
 
256
obsolete_1(httpd, start, 0)           -> {removed,{inets,start,[2,3]},"R14B"};
 
257
obsolete_1(httpd, start, 1)           -> {removed,{inets,start,[2,3]},"R14B"};
 
258
obsolete_1(httpd, start_link, 0)      -> {removed,{inets,start,[2,3]},"R14B"};
 
259
obsolete_1(httpd, start_link, 1)      -> {removed,{inets,start,[2,3]},"R14B"};
 
260
obsolete_1(httpd, start_child, 0)     -> {removed,{inets,start,[2,3]},"R14B"};
 
261
obsolete_1(httpd, start_child, 1)     -> {removed,{inets,start,[2,3]},"R14B"};
 
262
obsolete_1(httpd, stop, 0)            -> {removed,{inets,stop,2},"R14B"};
 
263
obsolete_1(httpd, stop, 1)            -> {removed,{inets,stop,2},"R14B"};
 
264
obsolete_1(httpd, stop, 2)            -> {removed,{inets,stop,2},"R14B"};
 
265
obsolete_1(httpd, stop_child, 0)      -> {removed,{inets,stop,2},"R14B"};
 
266
obsolete_1(httpd, stop_child, 1)      -> {removed,{inets,stop,2},"R14B"};
 
267
obsolete_1(httpd, stop_child, 2)      -> {removed,{inets,stop,2},"R14B"};
 
268
obsolete_1(httpd, restart, 0)         -> {removed,{httpd,reload_config,2},"R14B"};
 
269
obsolete_1(httpd, restart, 1)         -> {removed,{httpd,reload_config,2},"R14B"};
 
270
obsolete_1(httpd, restart, 2)         -> {removed,{httpd,reload_config,2},"R14B"};
 
271
obsolete_1(httpd, block, 0)           -> {removed,{httpd,reload_config,2},"R14B"};
 
272
obsolete_1(httpd, block, 1)           -> {removed,{httpd,reload_config,2},"R14B"};
 
273
obsolete_1(httpd, block, 2)           -> {removed,{httpd,reload_config,2},"R14B"};
 
274
obsolete_1(httpd, block, 3)           -> {removed,{httpd,reload_config,2},"R14B"};
 
275
obsolete_1(httpd, block, 4)           -> {removed,{httpd,reload_config,2},"R14B"};
 
276
obsolete_1(httpd, unblock, 0)         -> {removed,{httpd,reload_config,2},"R14B"};
 
277
obsolete_1(httpd, unblock, 1)         -> {removed,{httpd,reload_config,2},"R14B"};
 
278
obsolete_1(httpd, unblock, 2)         -> {removed,{httpd,reload_config,2},"R14B"};
261
279
obsolete_1(httpd_util, key1search, 2) -> {removed,{proplists,get_value,2},"R13B"};
262
280
obsolete_1(httpd_util, key1search, 3) -> {removed,{proplists,get_value,3},"R13B"};
263
 
obsolete_1(ftp, open, 3)          -> {deprecated,{inets,start,[2,3]},"R14B"};
264
 
obsolete_1(ftp, force_active, 1)  -> {deprecated,{inets,start,[2,3]},"R14B"};
 
281
obsolete_1(ftp, open, 3)              -> {removed,{inets,start,[2,3]},"R14B"};
 
282
obsolete_1(ftp, force_active, 1)      -> {removed,{inets,start,[2,3]},"R14B"};
265
283
 
266
284
%% Added in R12B-4.
267
285
obsolete_1(ssh_cm, connect, A) when 1 =< A, A =< 3 ->
268
 
    {deprecated,{ssh,connect,A},"R14B"};
 
286
    {removed,{ssh,connect,A},"R14B"};
269
287
obsolete_1(ssh_cm, listen, A) when 2 =< A, A =< 4 ->
270
 
    {deprecated,{ssh,daemon,A},"R14B"};
 
288
    {removed,{ssh,daemon,A},"R14B"};
271
289
obsolete_1(ssh_cm, stop_listener, 1) ->
272
 
    {deprecated,{ssh,stop_listener,[1,2]},"R14B"};
 
290
    {removed,{ssh,stop_listener,[1,2]},"R14B"};
273
291
obsolete_1(ssh_cm, session_open, A) when A =:= 2; A =:= 4 ->
274
 
    {deprecated,{ssh_connection,session_channel,A},"R14B"};
 
292
    {removed,{ssh_connection,session_channel,A},"R14B"};
275
293
obsolete_1(ssh_cm, direct_tcpip, A) when A =:= 6; A =:= 8 ->
276
 
    {deprecated,{ssh_connection,direct_tcpip,A}};
 
294
    {removed,{ssh_connection,direct_tcpip,A}};
277
295
obsolete_1(ssh_cm, tcpip_forward, 3) ->
278
 
    {deprecated,{ssh_connection,tcpip_forward,3},"R14B"};
 
296
    {removed,{ssh_connection,tcpip_forward,3},"R14B"};
279
297
obsolete_1(ssh_cm, cancel_tcpip_forward, 3) ->
280
 
    {deprecated,{ssh_connection,cancel_tcpip_forward,3},"R14B"};
 
298
    {removed,{ssh_connection,cancel_tcpip_forward,3},"R14B"};
281
299
obsolete_1(ssh_cm, open_pty, A) when A =:= 3; A =:= 7; A =:= 9 ->
282
 
    {deprecated,{ssh_connection,open_pty,A},"R14"};
 
300
    {removed,{ssh_connection,open_pty,A},"R14"};
283
301
obsolete_1(ssh_cm, setenv, 5) ->
284
 
    {deprecated,{ssh_connection,setenv,5},"R14B"};
 
302
    {removed,{ssh_connection,setenv,5},"R14B"};
285
303
obsolete_1(ssh_cm, shell, 2) ->
286
 
    {deprecated,{ssh_connection,shell,2},"R14B"};
 
304
    {removed,{ssh_connection,shell,2},"R14B"};
287
305
obsolete_1(ssh_cm, exec, 4) ->
288
 
    {deprecated,{ssh_connection,exec,4},"R14B"};
 
306
    {removed,{ssh_connection,exec,4},"R14B"};
289
307
obsolete_1(ssh_cm, subsystem, 4) ->
290
 
    {deprecated,{ssh_connection,subsystem,4},"R14B"};
 
308
    {removed,{ssh_connection,subsystem,4},"R14B"};
291
309
obsolete_1(ssh_cm, winch, A) when A =:= 4; A =:= 6 ->
292
 
    {deprecated,{ssh_connection,window_change,A},"R14B"};
 
310
    {removed,{ssh_connection,window_change,A},"R14B"};
293
311
obsolete_1(ssh_cm, signal, 3) ->
294
 
    {deprecated,{ssh_connection,signal,3},"R14B"};
 
312
    {removed,{ssh_connection,signal,3},"R14B"};
295
313
obsolete_1(ssh_cm, attach, A) when A =:= 2; A =:= 3 ->
296
 
    {deprecated,{ssh,attach,A}};
 
314
    {removed,{ssh,attach,A}};
297
315
obsolete_1(ssh_cm, detach, 2) ->
298
 
    {deprecated,"no longer useful; will be removed in R14B"};
 
316
    {removed,"no longer useful; will be removed in R14B"};
299
317
obsolete_1(ssh_cm, set_user_ack, 4) ->
300
 
    {deprecated,"no longer useful; will be removed in R14B"};
 
318
    {removed,"no longer useful; will be removed in R14B"};
301
319
obsolete_1(ssh_cm, adjust_window, 3) ->
302
 
    {deprecated,{ssh_connection,adjust_window,3},"R14B"};
 
320
    {removed,{ssh_connection,adjust_window,3},"R14B"};
303
321
obsolete_1(ssh_cm, close, 2) ->
304
 
    {deprecated,{ssh_connection,close,2},"R14B"};
 
322
    {removed,{ssh_connection,close,2},"R14B"};
305
323
obsolete_1(ssh_cm, stop, 1) ->
306
 
    {deprecated,{ssh,close,1},"R14B"};
 
324
    {removed,{ssh,close,1},"R14B"};
307
325
obsolete_1(ssh_cm, send_eof, 2) ->
308
 
    {deprecated,{ssh_connection,send_eof,2},"R14B"};
 
326
    {removed,{ssh_connection,send_eof,2},"R14B"};
309
327
obsolete_1(ssh_cm, send, A) when A =:= 3; A =:= 4 ->
310
 
    {deprecated,{ssh_connection,send,A},"R14B"};
 
328
    {removed,{ssh_connection,send,A},"R14B"};
311
329
obsolete_1(ssh_cm, send_ack, A) when 3 =< A, A =< 5 ->
312
 
    {deprecated,{ssh_connection,send,[3,4]},"R14B"};
 
330
    {removed,{ssh_connection,send,[3,4]},"R14B"};
313
331
obsolete_1(ssh_ssh, connect, A) when 1 =< A, A =< 3 ->
314
 
    {deprecated,{ssh,shell,A},"R14B"};
 
332
    {removed,{ssh,shell,A},"R14B"};
315
333
obsolete_1(ssh_sshd, listen, A) when 0 =< A, A =< 3 ->
316
 
    {deprecated,{ssh,daemon,[1,2,3]},"R14"};
 
334
    {removed,{ssh,daemon,[1,2,3]},"R14"};
317
335
obsolete_1(ssh_sshd, stop, 1) ->
318
 
    {deprecated,{ssh,stop_listener,1}};
 
336
    {removed,{ssh,stop_listener,1}};
319
337
 
320
338
%% Added in R13A.
321
339
obsolete_1(regexp, _, _) ->
322
340
    {deprecated, "the regexp module is deprecated (will be removed in R15A); use the re module instead"};
323
341
 
324
342
obsolete_1(lists, flat_length, 1) ->
325
 
    {deprecated,{lists,flatlength,1},"R14"};
 
343
    {removed,{lists,flatlength,1},"R14"};
326
344
 
327
345
obsolete_1(ssh_sftp, connect, A) when 1 =< A, A =< 3 ->
328
 
    {deprecated,{ssh_sftp,start_channel,A},"R14B"};
 
346
    {removed,{ssh_sftp,start_channel,A},"R14B"};
329
347
obsolete_1(ssh_sftp, stop, 1) ->
330
 
    {deprecated,{ssh_sftp,stop_channel,1},"R14B"};
 
348
    {removed,{ssh_sftp,stop_channel,1},"R14B"};
331
349
 
332
350
%% Added in R13B01.
333
351
obsolete_1(ssl_pkix, decode_cert_file, A) when A =:= 1; A =:= 2 ->
334
 
    {deprecated,"deprecated (will be removed in R14B); use public_key:pem_to_der/1 and public_key:pkix_decode_cert/2 instead"};
 
352
    {removed,"removed in R14A; use public_key:pem_to_der/1 and public_key:pkix_decode_cert/2 instead"};
335
353
obsolete_1(ssl_pkix, decode_cert, A) when A =:= 1; A =:= 2 ->
336
 
    {deprecated,{public_key,pkix_decode_cert,2},"R14B"};
337
 
    
 
354
    {removed,{public_key,pkix_decode_cert,2},"R14A"};
 
355
 
 
356
%% Added in R13B04.
 
357
obsolete_1(erlang, concat_binary, 1) ->
 
358
    {deprecated,{erlang,list_to_binary,1},"R15B"};
 
359
 
 
360
%% Added in R14A.
 
361
obsolete_1(ssl, peercert, 2) ->
 
362
    {deprecated,"deprecated (will be removed in R15A); use ssl:peercert/1 and public_key:pkix_decode_cert/2 instead"};
 
363
 
 
364
%% Added in R14B.
 
365
obsolete_1(public_key, pem_to_der, 1) ->
 
366
    {deprecated,"deprecated (will be removed in R15A); use file:read_file/1 and public_key:pem_decode/1"};
 
367
obsolete_1(public_key, decode_private_key, A) when A =:= 1; A =:= 2 ->
 
368
    {deprecated,{public_key,pem_entry_decode,1},"R15A"};
 
369
 
338
370
obsolete_1(_, _, _) ->
339
371
    no.
340
372