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

« back to all changes in this revision

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

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

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
 
%% ``The contents of this file are subject to the Erlang Public License,
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 1999-2009. All Rights Reserved.
 
5
%% 
 
6
%% The contents of this file are subject to the Erlang Public License,
2
7
%% Version 1.1, (the "License"); you may not use this file except in
3
8
%% compliance with the License. You should have received a copy of the
4
9
%% Erlang Public License along with this software. If not, it can be
5
 
%% retrieved via the world wide web at http://www.erlang.org/.
 
10
%% retrieved online at http://www.erlang.org/.
6
11
%% 
7
12
%% Software distributed under the License is distributed on an "AS IS"
8
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
9
14
%% the License for the specific language governing rights and limitations
10
15
%% under the License.
11
16
%% 
12
 
%% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
13
 
%% Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
14
 
%% AB. All Rights Reserved.''
15
 
%% 
16
 
%%     $Id$
 
17
%% %CopyrightEnd%
17
18
%%
18
19
-module(otp_internal).
19
20
 
219
220
obsolete_1(httpd_util, to_lower, 1) ->
220
221
    {removed, {string, to_lower, 1}, "R12B"};
221
222
obsolete_1(erlang, is_constant, 1) ->
222
 
    {deprecated, "Deprecated; will be removed in R13B"};
 
223
    {removed, "Removed in R13B"};
223
224
 
224
225
%% Added in R12B-0.
225
226
obsolete_1(ssl, port, 1) ->
226
 
    {deprecated, {ssl, sockname, 1}, "R13B"};
 
227
    {removed, {ssl, sockname, 1}, "R13B"};
227
228
obsolete_1(ssl, accept, A) when A =:= 1; A =:= 2 ->
228
 
    {deprecated, "deprecated; use ssl:transport_accept/1,2 and ssl:ssl_accept/1,2"};
 
229
    {removed, "deprecated; use ssl:transport_accept/1,2 and ssl:ssl_accept/1,2"};
229
230
obsolete_1(erlang, fault, 1) ->
230
 
    {deprecated, {erlang,error,1}, "R13B"};
 
231
    {removed, {erlang,error,1}, "R13B"};
231
232
obsolete_1(erlang, fault, 2) ->
232
 
    {deprecated, {erlang,error,2}, "R13B"};
 
233
    {removed, {erlang,error,2}, "R13B"};
233
234
 
234
235
%% Added in R12B-2.
235
236
obsolete_1(file, rawopen, 2) ->
236
 
    {deprecated, "deprecated (will be removed in R13B); use file:open/2 with the raw option"};
 
237
    {removed, "deprecated (will be removed in R13B); use file:open/2 with the raw option"};
237
238
 
238
239
obsolete_1(httpd, start, 0)       -> {deprecated,{inets,start,[2,3]},"R14B"};
239
240
obsolete_1(httpd, start, 1)       -> {deprecated,{inets,start,[2,3]},"R14B"};
257
258
obsolete_1(httpd, unblock, 0)     -> {deprecated,{httpd,reload_config,2},"R14B"};
258
259
obsolete_1(httpd, unblock, 1)     -> {deprecated,{httpd,reload_config,2},"R14B"};
259
260
obsolete_1(httpd, unblock, 2)     -> {deprecated,{httpd,reload_config,2},"R14B"};
260
 
obsolete_1(httpd_util, key1search, 2) -> {deprecated,{proplists,get_value,2},"R13B"};
261
 
obsolete_1(httpd_util, key1search, 3) -> {deprecated,{proplists,get_value,3},"R13B"};
 
261
obsolete_1(httpd_util, key1search, 2) -> {removed,{proplists,get_value,2},"R13B"};
 
262
obsolete_1(httpd_util, key1search, 3) -> {removed,{proplists,get_value,3},"R13B"};
262
263
obsolete_1(ftp, open, 1)          -> {deprecated,{inets,start,[2,3]},"R14B"};
263
264
obsolete_1(ftp, open, 2)          -> {deprecated,{inets,start,[2,3]},"R14B"};
264
265
obsolete_1(ftp, open, 3)          -> {deprecated,{inets,start,[2,3]},"R14B"};
312
313
    {deprecated,{ssh_connection,send,A},"R14B"};
313
314
obsolete_1(ssh_cm, send_ack, A) when 3 =< A, A =< 5 ->
314
315
    {deprecated,{ssh_connection,send,[3,4]},"R14B"};
315
 
obsolete_1(ssh_ssh, connect, A) when 1 =< A, 3 =< 3 ->
 
316
obsolete_1(ssh_ssh, connect, A) when 1 =< A, A =< 3 ->
316
317
    {deprecated,{ssh,shell,A},"R14B"};
317
318
obsolete_1(ssh_sshd, listen, A) when 0 =< A, A =< 3 ->
318
319
    {deprecated,{ssh,daemon,[1,2,3]},"R14"};
319
320
obsolete_1(ssh_sshd, stop, 1) ->
320
321
    {deprecated,{ssh,stop_listener,1}};
321
322
 
 
323
%% Added in R13A.
 
324
obsolete_1(regexp, _, _) ->
 
325
    {deprecated, "the regexp module is deprecated (will be removed in R15A); use the re module instead"};
 
326
 
 
327
obsolete_1(lists, flat_length, 1) ->
 
328
    {deprecated,{lists,flatlength,1},"R14"};
 
329
 
 
330
obsolete_1(ssh_sftp, connect, A) when 1 =< A, A =< 3 ->
 
331
    {deprecated,{ssh_sftp,start_channel,A},"R14B"};
 
332
obsolete_1(ssh_sftp, stop, 1) ->
 
333
    {deprecated,{ssh_sftp,stop_channel,1},"R14B"};
 
334
    
322
335
obsolete_1(_, _, _) ->
323
336
    no.
324
337