diff options
Diffstat (limited to 'lib/stdlib/src')
-rw-r--r-- | lib/stdlib/src/base64.erl | 113 | ||||
-rw-r--r-- | lib/stdlib/src/c.erl | 52 | ||||
-rw-r--r-- | lib/stdlib/src/erl_lint.erl | 22 | ||||
-rw-r--r-- | lib/stdlib/src/erl_posix_msg.erl | 285 | ||||
-rw-r--r-- | lib/stdlib/src/escript.erl | 4 | ||||
-rw-r--r-- | lib/stdlib/src/filename.erl | 14 | ||||
-rw-r--r-- | lib/stdlib/src/io.erl | 38 | ||||
-rw-r--r-- | lib/stdlib/src/re.erl | 42 | ||||
-rw-r--r-- | lib/stdlib/src/supervisor.erl | 115 |
9 files changed, 392 insertions, 293 deletions
diff --git a/lib/stdlib/src/base64.erl b/lib/stdlib/src/base64.erl index ebef998ee1..a14a72ac6d 100644 --- a/lib/stdlib/src/base64.erl +++ b/lib/stdlib/src/base64.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 2007-2009. All Rights Reserved. +%% Copyright Ericsson AB 2007-2011. All Rights Reserved. %% %% The contents of this file are subject to the Erlang Public License, %% Version 1.1, (the "License"); you may not use this file except in @@ -114,7 +114,7 @@ decode(List) when is_list(List) -> mime_decode(Bin) when is_binary(Bin) -> mime_decode_binary(<<>>, Bin); mime_decode(List) when is_list(List) -> - list_to_binary(mime_decode_l(List)). + mime_decode(list_to_binary(List)). -spec decode_l(string()) -> string(). @@ -125,7 +125,7 @@ decode_l(List) -> -spec mime_decode_l(string()) -> string(). mime_decode_l(List) -> - L = strip_illegal(List, []), + L = strip_illegal(List, [], 0), decode(L, []). %%------------------------------------------------------------------------- @@ -198,6 +198,9 @@ decode_binary(Result, <<>>) -> true = is_binary(Result), Result. +%% Skipping pad character if not at end of string. Also liberal about +%% excess padding and skipping of other illegal (non-base64 alphabet) +%% characters. See section 3.3 of RFC4648 mime_decode_binary(Result, <<0:8,T/bits>>) -> mime_decode_binary(Result, T); mime_decode_binary(Result0, <<C:8,T/bits>>) -> @@ -205,15 +208,27 @@ mime_decode_binary(Result0, <<C:8,T/bits>>) -> Bits when is_integer(Bits) -> mime_decode_binary(<<Result0/bits,Bits:6>>, T); eq -> - case tail_contains_equal(T) of - true -> - Split = byte_size(Result0) - 1, - <<Result:Split/bytes,_:4>> = Result0, - Result; - false -> - Split = byte_size(Result0) - 1, - <<Result:Split/bytes,_:2>> = Result0, - Result + case tail_contains_more(T, false) of + {<<>>, Eq} -> + %% No more valid data. + case bit_size(Result0) rem 8 of + 0 -> + %% '====' is not uncommon. + Result0; + 4 when Eq -> + %% enforce at least one more '=' only ignoring illegals and spacing + Split = byte_size(Result0) - 1, + <<Result:Split/bytes,_:4>> = Result0, + Result; + 2 -> + %% remove 2 bits + Split = byte_size(Result0) - 1, + <<Result:Split/bytes,_:2>> = Result0, + Result + end; + {More, _} -> + %% More valid data, skip the eq as invalid + mime_decode_binary(Result0, More) end; _ -> mime_decode_binary(Result0, T) @@ -262,31 +277,63 @@ strip_ws(<<$\s,T/binary>>) -> strip_ws(T); strip_ws(T) -> T. -strip_illegal([0|Cs], A) -> - strip_illegal(Cs, A); -strip_illegal([C|Cs], A) -> +%% Skipping pad character if not at end of string. Also liberal about +%% excess padding and skipping of other illegal (non-base64 alphabet) +%% characters. See section 3.3 of RFC4648 +strip_illegal([], A, _Cnt) -> + A; +strip_illegal([0|Cs], A, Cnt) -> + strip_illegal(Cs, A, Cnt); +strip_illegal([C|Cs], A, Cnt) -> case element(C, ?DECODE_MAP) of - bad -> strip_illegal(Cs, A); - ws -> strip_illegal(Cs, A); - eq -> strip_illegal_end(Cs, [$=|A]); - _ -> strip_illegal(Cs, [C|A]) - end; -strip_illegal([], A) -> A. + bad -> + strip_illegal(Cs, A, Cnt); + ws -> + strip_illegal(Cs, A, Cnt); + eq -> + case {tail_contains_more(Cs, false), Cnt rem 4} of + {{[], _}, 0} -> + A; %% Ignore extra = + {{[], true}, 2} -> + [$=|[$=|A]]; %% 'XX==' + {{[], _}, 3} -> + [$=|A]; %% 'XXX=' + {{[H|T], _}, _} -> + %% more data, skip equals + strip_illegal(T, [H|A], Cnt+1) + end; + _ -> + strip_illegal(Cs, [C|A], Cnt+1) + end. -strip_illegal_end([0|Cs], A) -> - strip_illegal_end(Cs, A); -strip_illegal_end([C|Cs], A) -> +%% Search the tail for more valid data and remember if we saw +%% another equals along the way. +tail_contains_more([], Eq) -> + {[], Eq}; +tail_contains_more(<<>>, Eq) -> + {<<>>, Eq}; +tail_contains_more([C|T]=More, Eq) -> case element(C, ?DECODE_MAP) of - bad -> strip_illegal(Cs, A); - ws -> strip_illegal(Cs, A); - eq -> [C|A]; - _ -> strip_illegal(Cs, [C|A]) + bad -> + tail_contains_more(T, Eq); + ws -> + tail_contains_more(T, Eq); + eq -> + tail_contains_more(T, true); + _ -> + {More, Eq} end; -strip_illegal_end([], A) -> A. - -tail_contains_equal(<<$=,_/binary>>) -> true; -tail_contains_equal(<<_,T/binary>>) -> tail_contains_equal(T); -tail_contains_equal(<<>>) -> false. +tail_contains_more(<<C:8,T/bits>> =More, Eq) -> + case element(C, ?DECODE_MAP) of + bad -> + tail_contains_more(T, Eq); + ws -> + tail_contains_more(T, Eq); + eq -> + tail_contains_more(T, true); + _ -> + {More, Eq} + end. %% accessors b64e(X) -> diff --git a/lib/stdlib/src/c.erl b/lib/stdlib/src/c.erl index d04d8f191f..235ea939a8 100644 --- a/lib/stdlib/src/c.erl +++ b/lib/stdlib/src/c.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2010. All Rights Reserved. +%% Copyright Ericsson AB 1996-2011. All Rights Reserved. %% %% The contents of this file are subject to the Erlang Public License, %% Version 1.1, (the "License"); you may not use this file except in @@ -42,31 +42,31 @@ -spec help() -> 'ok'. help() -> - format("bt(Pid) -- stack backtrace for a process\n" - "c(File) -- compile and load code in <File>\n" - "cd(Dir) -- change working directory\n" - "flush() -- flush any messages sent to the shell\n" - "help() -- help info\n" - "i() -- information about the system\n" - "ni() -- information about the networked system\n" - "i(X,Y,Z) -- information about pid <X,Y,Z>\n" - "l(Module) -- load or reload module\n" - "lc([File]) -- compile a list of Erlang modules\n" - "ls() -- list files in the current directory\n" - "ls(Dir) -- list files in directory <Dir>\n" - "m() -- which modules are loaded\n" - "m(Mod) -- information about module <Mod>\n" - "memory() -- memory allocation information\n" - "memory(T) -- memory allocation information of type <T>\n" - "nc(File) -- compile and load code in <File> on all nodes\n" - "nl(Module) -- load module on all nodes\n" - "pid(X,Y,Z) -- convert X,Y,Z to a Pid\n" - "pwd() -- print working directory\n" - "q() -- quit - shorthand for init:stop()\n" - "regs() -- information about registered processes\n" - "nregs() -- information about all registered processes\n" - "xm(M) -- cross reference check a module\n" - "y(File) -- generate a Yecc parser\n"). + io:put_chars(<<"bt(Pid) -- stack backtrace for a process\n" + "c(File) -- compile and load code in <File>\n" + "cd(Dir) -- change working directory\n" + "flush() -- flush any messages sent to the shell\n" + "help() -- help info\n" + "i() -- information about the system\n" + "ni() -- information about the networked system\n" + "i(X,Y,Z) -- information about pid <X,Y,Z>\n" + "l(Module) -- load or reload module\n" + "lc([File]) -- compile a list of Erlang modules\n" + "ls() -- list files in the current directory\n" + "ls(Dir) -- list files in directory <Dir>\n" + "m() -- which modules are loaded\n" + "m(Mod) -- information about module <Mod>\n" + "memory() -- memory allocation information\n" + "memory(T) -- memory allocation information of type <T>\n" + "nc(File) -- compile and load code in <File> on all nodes\n" + "nl(Module) -- load module on all nodes\n" + "pid(X,Y,Z) -- convert X,Y,Z to a Pid\n" + "pwd() -- print working directory\n" + "q() -- quit - shorthand for init:stop()\n" + "regs() -- information about registered processes\n" + "nregs() -- information about all registered processes\n" + "xm(M) -- cross reference check a module\n" + "y(File) -- generate a Yecc parser\n">>). %% c(FileName) %% Compile a file/module. diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl index 0c2d3db8ec..cfb9f0ca98 100644 --- a/lib/stdlib/src/erl_lint.erl +++ b/lib/stdlib/src/erl_lint.erl @@ -2,7 +2,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2010. All Rights Reserved. +%% Copyright Ericsson AB 1996-2011. All Rights Reserved. %% %% The contents of this file are subject to the Erlang Public License, %% Version 1.1, (the "License"); you may not use this file except in @@ -60,6 +60,10 @@ value_option(Flag, Default, On, OnVal, Off, OffVal, Opts) -> (_Opt, Def) -> Def end, Default, Opts). +%% The maximum number of arguments allowed for a function. + +-define(MAX_ARGUMENTS, 255). + %% The error and warning info structures, {Line,Module,Descriptor}, %% are kept in their seperate fields in the lint state record together %% with the name of the file (when a new file is entered, marked by @@ -226,6 +230,9 @@ format_error({obsolete_guard, {F, A}}) -> io_lib:format("~p/~p obsolete", [F, A]); format_error({reserved_for_future,K}) -> io_lib:format("atom ~w: future reserved keyword - rename or quote", [K]); +format_error({too_many_arguments,Arity}) -> + io_lib:format("too many arguments (~w) - " + "maximum allowed is ~w", [Arity,?MAX_ARGUMENTS]); %% --- patterns and guards --- format_error(illegal_pattern) -> "illegal pattern"; format_error(illegal_bin_pattern) -> @@ -1307,13 +1314,18 @@ define_function(Line, Name, Arity, St0) -> true -> add_error(Line, {redefine_function,NA}, St1); false -> - St2 = St1#lint{defined=gb_sets:add_element(NA, St1#lint.defined)}, - case imported(Name, Arity, St2) of - {yes,_M} -> add_error(Line, {define_import,NA}, St2); - no -> St2 + St2 = function_check_max_args(Line, Arity, St1), + St3 = St2#lint{defined=gb_sets:add_element(NA, St2#lint.defined)}, + case imported(Name, Arity, St3) of + {yes,_M} -> add_error(Line, {define_import,NA}, St3); + no -> St3 end end. +function_check_max_args(Line, Arity, St) when Arity > ?MAX_ARGUMENTS -> + add_error(Line, {too_many_arguments,Arity}, St); +function_check_max_args(_, _, St) -> St. + %% clauses([Clause], VarTable, State) -> {VarTable, State}. clauses(Cs, Vt, St) -> diff --git a/lib/stdlib/src/erl_posix_msg.erl b/lib/stdlib/src/erl_posix_msg.erl index fe981b23a7..909cc1d102 100644 --- a/lib/stdlib/src/erl_posix_msg.erl +++ b/lib/stdlib/src/erl_posix_msg.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1997-2009. All Rights Reserved. +%% Copyright Ericsson AB 1997-2010. All Rights Reserved. %% %% The contents of this file are subject to the Erlang Public License, %% Version 1.1, (the "License"); you may not use this file except in @@ -24,143 +24,146 @@ -spec message(atom()) -> string(). -message(e2big) -> "argument list too long"; -message(eacces) -> "permission denied"; -message(eaddrinuse) -> "address already in use"; -message(eaddrnotavail) -> "can't assign requested address"; -message(eadv) -> "advertise error"; -message(eafnosupport) -> "address family not supported by protocol family"; -message(eagain) -> "resource temporarily unavailable"; -message(ealign) -> "EALIGN"; -message(ealready) -> "operation already in progress"; -message(ebade) -> "bad exchange descriptor"; -message(ebadf) -> "bad file number"; -message(ebadfd) -> "file descriptor in bad state"; -message(ebadmsg) -> "not a data message"; -message(ebadr) -> "bad request descriptor"; -message(ebadrpc) -> "RPC structure is bad"; -message(ebadrqc) -> "bad request code"; -message(ebadslt) -> "invalid slot"; -message(ebfont) -> "bad font file format"; -message(ebusy) -> "file busy"; -message(echild) -> "no children"; -message(echrng) -> "channel number out of range"; -message(ecomm) -> "communication error on send"; -message(econnaborted) -> "software caused connection abort"; -message(econnrefused) -> "connection refused"; -message(econnreset) -> "connection reset by peer"; -message(edeadlk) -> "resource deadlock avoided"; -message(edeadlock) -> "resource deadlock avoided"; -message(edestaddrreq) -> "destination address required"; -message(edirty) -> "mounting a dirty fs w/o force"; -message(edom) -> "math argument out of range"; -message(edotdot) -> "cross mount point"; -message(edquot) -> "disk quota exceeded"; -message(eduppkg) -> "duplicate package name"; -message(eexist) -> "file already exists"; -message(efault) -> "bad address in system call argument"; -message(efbig) -> "file too large"; -message(ehostdown) -> "host is down"; -message(ehostunreach) -> "host is unreachable"; -message(eidrm) -> "identifier removed"; -message(einit) -> "initialization error"; -message(einprogress) -> "operation now in progress"; -message(eintr) -> "interrupted system call"; -message(einval) -> "invalid argument"; -message(eio) -> "I/O error"; -message(eisconn) -> "socket is already connected"; -message(eisdir) -> "illegal operation on a directory"; -message(eisnam) -> "is a name file"; -message(elbin) -> "ELBIN"; -message(el2hlt) -> "level 2 halted"; -message(el2nsync) -> "level 2 not synchronized"; -message(el3hlt) -> "level 3 halted"; -message(el3rst) -> "level 3 reset"; -message(elibacc) -> "can not access a needed shared library"; -message(elibbad) -> "accessing a corrupted shared library"; -message(elibexec) -> "can not exec a shared library directly"; -message(elibmax) -> - "attempting to link in more shared libraries than system limit"; -message(elibscn) -> ".lib section in a.out corrupted"; -message(elnrng) -> "link number out of range"; -message(eloop) -> "too many levels of symbolic links"; -message(emfile) -> "too many open files"; -message(emlink) -> "too many links"; -message(emsgsize) -> "message too long"; -message(emultihop) -> "multihop attempted"; -message(enametoolong) -> "file name too long"; -message(enavail) -> "not available"; -message(enet) -> "ENET"; -message(enetdown) -> "network is down"; -message(enetreset) -> "network dropped connection on reset"; -message(enetunreach) -> "network is unreachable"; -message(enfile) -> "file table overflow"; -message(enoano) -> "anode table overflow"; -message(enobufs) -> "no buffer space available"; -message(enocsi) -> "no CSI structure available"; -message(enodata) -> "no data available"; -message(enodev) -> "no such device"; -message(enoent) -> "no such file or directory"; -message(enoexec) -> "exec format error"; -message(enolck) -> "no locks available"; -message(enolink) -> "link has be severed"; -message(enomem) -> "not enough memory"; -message(enomsg) -> "no message of desired type"; -message(enonet) -> "machine is not on the network"; -message(enopkg) -> "package not installed"; -message(enoprotoopt) -> "bad proocol option"; -message(enospc) -> "no space left on device"; -message(enosr) -> "out of stream resources or not a stream device"; -message(enosym) -> "unresolved symbol name"; -message(enosys) -> "function not implemented"; -message(enotblk) -> "block device required"; -message(enotconn) -> "socket is not connected"; -message(enotdir) -> "not a directory"; -message(enotempty) -> "directory not empty"; -message(enotnam) -> "not a name file"; -message(enotsock) -> "socket operation on non-socket"; -message(enotsup) -> "operation not supported"; -message(enotty) -> "inappropriate device for ioctl"; -message(enotuniq) -> "name not unique on network"; -message(enxio) -> "no such device or address"; -message(eopnotsupp) -> "operation not supported on socket"; -message(eperm) -> "not owner"; -message(epfnosupport) -> "protocol family not supported"; -message(epipe) -> "broken pipe"; -message(eproclim) -> "too many processes"; -message(eprocunavail) -> "bad procedure for program"; -message(eprogmismatch) -> "program version wrong"; -message(eprogunavail) -> "RPC program not available"; -message(eproto) -> "protocol error"; -message(eprotonosupport) -> "protocol not suppored"; -message(eprototype) -> "protocol wrong type for socket"; -message(erange) -> "math result unrepresentable"; -message(erefused) -> "EREFUSED"; -message(eremchg) -> "remote address changed"; -message(eremdev) -> "remote device"; -message(eremote) -> "pathname hit remote file system"; -message(eremoteio) -> "remote i/o error"; -message(eremoterelease) -> "EREMOTERELEASE"; -message(erofs) -> "read-only file system"; -message(erpcmismatch) -> "RPC version is wrong"; -message(erremote) -> "object is remote"; -message(eshutdown) -> "can't send after socket shutdown"; -message(esocktnosupport) -> "socket type not supported"; -message(espipe) -> "invalid seek"; -message(esrch) -> "no such process"; -message(esrmnt) -> "srmount error"; -message(estale) -> "stale remote file handle"; -message(esuccess) -> "Error 0"; -message(etime) -> "timer expired"; -message(etimedout) -> "connection timed out"; -message(etoomanyrefs) -> "too many references: can't splice"; -message(etxtbsy) -> "text file or pseudo-device busy"; -message(euclean) -> "structure needs cleaning"; -message(eunatch) -> "protocol driver not attached"; -message(eusers) -> "too many users"; -message(eversion) -> "version mismatch"; -message(ewouldblock) -> "operation would block"; -message(exdev) -> "cross-domain link"; -message(exfull) -> "message tables full"; -message(nxdomain) -> "non-existing domain"; -message(_) -> "unknown POSIX error". +message(T) -> + binary_to_list(message_1(T)). + +message_1(e2big) -> <<"argument list too long">>; +message_1(eacces) -> <<"permission denied">>; +message_1(eaddrinuse) -> <<"address already in use">>; +message_1(eaddrnotavail) -> <<"can't assign requested address">>; +message_1(eadv) -> <<"advertise error">>; +message_1(eafnosupport) -> <<"address family not supported by protocol family">>; +message_1(eagain) -> <<"resource temporarily unavailable">>; +message_1(ealign) -> <<"EALIGN">>; +message_1(ealready) -> <<"operation already in progress">>; +message_1(ebade) -> <<"bad exchange descriptor">>; +message_1(ebadf) -> <<"bad file number">>; +message_1(ebadfd) -> <<"file descriptor in bad state">>; +message_1(ebadmsg) -> <<"not a data message">>; +message_1(ebadr) -> <<"bad request descriptor">>; +message_1(ebadrpc) -> <<"RPC structure is bad">>; +message_1(ebadrqc) -> <<"bad request code">>; +message_1(ebadslt) -> <<"invalid slot">>; +message_1(ebfont) -> <<"bad font file format">>; +message_1(ebusy) -> <<"file busy">>; +message_1(echild) -> <<"no children">>; +message_1(echrng) -> <<"channel number out of range">>; +message_1(ecomm) -> <<"communication error on send">>; +message_1(econnaborted) -> <<"software caused connection abort">>; +message_1(econnrefused) -> <<"connection refused">>; +message_1(econnreset) -> <<"connection reset by peer">>; +message_1(edeadlk) -> <<"resource deadlock avoided">>; +message_1(edeadlock) -> <<"resource deadlock avoided">>; +message_1(edestaddrreq) -> <<"destination address required">>; +message_1(edirty) -> <<"mounting a dirty fs w/o force">>; +message_1(edom) -> <<"math argument out of range">>; +message_1(edotdot) -> <<"cross mount point">>; +message_1(edquot) -> <<"disk quota exceeded">>; +message_1(eduppkg) -> <<"duplicate package name">>; +message_1(eexist) -> <<"file already exists">>; +message_1(efault) -> <<"bad address in system call argument">>; +message_1(efbig) -> <<"file too large">>; +message_1(ehostdown) -> <<"host is down">>; +message_1(ehostunreach) -> <<"host is unreachable">>; +message_1(eidrm) -> <<"identifier removed">>; +message_1(einit) -> <<"initialization error">>; +message_1(einprogress) -> <<"operation now in progress">>; +message_1(eintr) -> <<"interrupted system call">>; +message_1(einval) -> <<"invalid argument">>; +message_1(eio) -> <<"I/O error">>; +message_1(eisconn) -> <<"socket is already connected">>; +message_1(eisdir) -> <<"illegal operation on a directory">>; +message_1(eisnam) -> <<"is a name file">>; +message_1(elbin) -> <<"ELBIN">>; +message_1(el2hlt) -> <<"level 2 halted">>; +message_1(el2nsync) -> <<"level 2 not synchronized">>; +message_1(el3hlt) -> <<"level 3 halted">>; +message_1(el3rst) -> <<"level 3 reset">>; +message_1(elibacc) -> <<"can not access a needed shared library">>; +message_1(elibbad) -> <<"accessing a corrupted shared library">>; +message_1(elibexec) -> <<"can not exec a shared library directly">>; +message_1(elibmax) -> + <<"attempting to link in more shared libraries than system limit">>; +message_1(elibscn) -> <<".lib section in a.out corrupted">>; +message_1(elnrng) -> <<"link number out of range">>; +message_1(eloop) -> <<"too many levels of symbolic links">>; +message_1(emfile) -> <<"too many open files">>; +message_1(emlink) -> <<"too many links">>; +message_1(emsgsize) -> <<"message too long">>; +message_1(emultihop) -> <<"multihop attempted">>; +message_1(enametoolong) -> <<"file name too long">>; +message_1(enavail) -> <<"not available">>; +message_1(enet) -> <<"ENET">>; +message_1(enetdown) -> <<"network is down">>; +message_1(enetreset) -> <<"network dropped connection on reset">>; +message_1(enetunreach) -> <<"network is unreachable">>; +message_1(enfile) -> <<"file table overflow">>; +message_1(enoano) -> <<"anode table overflow">>; +message_1(enobufs) -> <<"no buffer space available">>; +message_1(enocsi) -> <<"no CSI structure available">>; +message_1(enodata) -> <<"no data available">>; +message_1(enodev) -> <<"no such device">>; +message_1(enoent) -> <<"no such file or directory">>; +message_1(enoexec) -> <<"exec format error">>; +message_1(enolck) -> <<"no locks available">>; +message_1(enolink) -> <<"link has be severed">>; +message_1(enomem) -> <<"not enough memory">>; +message_1(enomsg) -> <<"no message of desired type">>; +message_1(enonet) -> <<"machine is not on the network">>; +message_1(enopkg) -> <<"package not installed">>; +message_1(enoprotoopt) -> <<"bad proocol option">>; +message_1(enospc) -> <<"no space left on device">>; +message_1(enosr) -> <<"out of stream resources or not a stream device">>; +message_1(enosym) -> <<"unresolved symbol name">>; +message_1(enosys) -> <<"function not implemented">>; +message_1(enotblk) -> <<"block device required">>; +message_1(enotconn) -> <<"socket is not connected">>; +message_1(enotdir) -> <<"not a directory">>; +message_1(enotempty) -> <<"directory not empty">>; +message_1(enotnam) -> <<"not a name file">>; +message_1(enotsock) -> <<"socket operation on non-socket">>; +message_1(enotsup) -> <<"operation not supported">>; +message_1(enotty) -> <<"inappropriate device for ioctl">>; +message_1(enotuniq) -> <<"name not unique on network">>; +message_1(enxio) -> <<"no such device or address">>; +message_1(eopnotsupp) -> <<"operation not supported on socket">>; +message_1(eperm) -> <<"not owner">>; +message_1(epfnosupport) -> <<"protocol family not supported">>; +message_1(epipe) -> <<"broken pipe">>; +message_1(eproclim) -> <<"too many processes">>; +message_1(eprocunavail) -> <<"bad procedure for program">>; +message_1(eprogmismatch) -> <<"program version wrong">>; +message_1(eprogunavail) -> <<"RPC program not available">>; +message_1(eproto) -> <<"protocol error">>; +message_1(eprotonosupport) -> <<"protocol not suppored">>; +message_1(eprototype) -> <<"protocol wrong type for socket">>; +message_1(erange) -> <<"math result unrepresentable">>; +message_1(erefused) -> <<"EREFUSED">>; +message_1(eremchg) -> <<"remote address changed">>; +message_1(eremdev) -> <<"remote device">>; +message_1(eremote) -> <<"pathname hit remote file system">>; +message_1(eremoteio) -> <<"remote i/o error">>; +message_1(eremoterelease) -> <<"EREMOTERELEASE">>; +message_1(erofs) -> <<"read-only file system">>; +message_1(erpcmismatch) -> <<"RPC version is wrong">>; +message_1(erremote) -> <<"object is remote">>; +message_1(eshutdown) -> <<"can't send after socket shutdown">>; +message_1(esocktnosupport) -> <<"socket type not supported">>; +message_1(espipe) -> <<"invalid seek">>; +message_1(esrch) -> <<"no such process">>; +message_1(esrmnt) -> <<"srmount error">>; +message_1(estale) -> <<"stale remote file handle">>; +message_1(esuccess) -> <<"Error 0">>; +message_1(etime) -> <<"timer expired">>; +message_1(etimedout) -> <<"connection timed out">>; +message_1(etoomanyrefs) -> <<"too many references: can't splice">>; +message_1(etxtbsy) -> <<"text file or pseudo-device busy">>; +message_1(euclean) -> <<"structure needs cleaning">>; +message_1(eunatch) -> <<"protocol driver not attached">>; +message_1(eusers) -> <<"too many users">>; +message_1(eversion) -> <<"version mismatch">>; +message_1(ewouldblock) -> <<"operation would block">>; +message_1(exdev) -> <<"cross-domain link">>; +message_1(exfull) -> <<"message tables full">>; +message_1(nxdomain) -> <<"non-existing domain">>; +message_1(_) -> <<"unknown POSIX error">>. diff --git a/lib/stdlib/src/escript.erl b/lib/stdlib/src/escript.erl index 99e454f593..7cb02afb11 100644 --- a/lib/stdlib/src/escript.erl +++ b/lib/stdlib/src/escript.erl @@ -570,9 +570,7 @@ parse_beam(S, File, HeaderSz, CheckOnly) -> forms_or_bin = Bin} end; {error, beam_lib, Reason} when is_tuple(Reason) -> - fatal(element(1, Reason)); - {error, beam_lib, Reason} -> - fatal(Reason) + fatal(element(1, Reason)) end. parse_source(S, File, Fd, StartLine, HeaderSz, CheckOnly) -> diff --git a/lib/stdlib/src/filename.erl b/lib/stdlib/src/filename.erl index e38b8957f2..24abf1e977 100644 --- a/lib/stdlib/src/filename.erl +++ b/lib/stdlib/src/filename.erl @@ -165,8 +165,6 @@ basename1([$/|[]], Tail, DirSep2) -> basename1([], Tail, DirSep2); basename1([$/|Rest], _Tail, DirSep2) -> basename1(Rest, [], DirSep2); -basename1([[_|_]=List|Rest], Tail, DirSep2) -> - basename1(List++Rest, Tail, DirSep2); basename1([DirSep2|Rest], Tail, DirSep2) when is_integer(DirSep2) -> basename1([$/|Rest], Tail, DirSep2); basename1([Char|Rest], Tail, DirSep2) when is_integer(Char) -> @@ -280,8 +278,6 @@ dirname(Name0) -> Name = flatten(Name0), dirname(Name, [], [], separators()). -dirname([[_|_]=List|Rest], Dir, File, Seps) -> - dirname(List++Rest, Dir, File, Seps); dirname([$/|Rest], Dir, File, Seps) -> dirname(Rest, File++Dir, [$/], Seps); dirname([DirSep|Rest], Dir, File, {DirSep,_}=Seps) when is_integer(DirSep) -> @@ -346,8 +342,6 @@ extension(Name) when is_binary(Name) -> [] end, case binary:matches(Name,[<<".">>]) of - nomatch -> % Bug in binary workaround :( - <<>>; [] -> <<>>; List -> @@ -479,6 +473,12 @@ maybe_remove_dirsep(Name, _) -> %% by a previous call to join/{1,2}. -spec append(file:filename(), file:name()) -> file:filename(). +append(Dir, Name) when is_binary(Dir), is_binary(Name) -> + <<Dir/binary,$/:8,Name/binary>>; +append(Dir, Name) when is_binary(Dir) -> + append(Dir,filename_string_to_binary(Name)); +append(Dir, Name) when is_binary(Name) -> + append(filename_string_to_binary(Dir),Name); append(Dir, Name) -> Dir ++ [$/|Name]. @@ -685,8 +685,6 @@ split([$/|Rest], Comp, Components, OsType) -> split(Rest, [], [lists:reverse(Comp)|Components], OsType); split([Char|Rest], Comp, Components, OsType) when is_integer(Char) -> split(Rest, [Char|Comp], Components, OsType); -split([List|Rest], Comp, Components, OsType) when is_list(List) -> - split(List++Rest, Comp, Components, OsType); split([], [], Components, _OsType) -> lists:reverse(Components); split([], Comp, Components, OsType) -> diff --git a/lib/stdlib/src/io.erl b/lib/stdlib/src/io.erl index 1d0f9374bc..3efa68ca09 100644 --- a/lib/stdlib/src/io.erl +++ b/lib/stdlib/src/io.erl @@ -39,6 +39,8 @@ -type device() :: atom() | pid(). -type prompt() :: atom() | string(). +-type error_description() :: term(). % Whatever the io-server sends. +-type request_error() :: {'error',error_description()}. %% XXX: Some uses of line() in this file may need to read erl_scan:location() -type line() :: pos_integer(). @@ -53,26 +55,12 @@ to_tuple(T) when is_tuple(T) -> T; to_tuple(T) -> {T}. -%% Problem: the variables Other, Name and Args may collide with surrounding -%% ones. -%% Give extra args to macro, being the variables to use. --define(O_REQUEST(Io, Request), - case request(Io, Request) of - {error, Reason} -> - [Name | Args] = tuple_to_list(to_tuple(Request)), - erlang:error(conv_reason(Name, Reason), [Name, Io | Args]); - Other -> - Other - end). - o_request(Io, Request, Func) -> case request(Io, Request) of {error, Reason} -> [_Name | Args] = tuple_to_list(to_tuple(Request)), - {'EXIT',{undef,[_Current|Mfas]}} = (catch erlang:error(undef)), - MFA = {io, Func, [Io | Args]}, - exit({conv_reason(Func, Reason),[MFA|Mfas]}); -% erlang:error(conv_reason(Name, Reason), [Name, Io | Args]); + {'EXIT',{get_stacktrace,[_Current|Mfas]}} = (catch erlang:error(get_stacktrace)), + erlang:raise(error, conv_reason(Func, Reason), [{io, Func, [Io | Args]}|Mfas]); Other -> Other end. @@ -299,32 +287,32 @@ format(Io, Format, Args) -> %% Scanning Erlang code. --spec scan_erl_exprs(prompt()) -> erl_scan:tokens_result(). +-spec scan_erl_exprs(prompt()) -> erl_scan:tokens_result() | request_error(). scan_erl_exprs(Prompt) -> scan_erl_exprs(default_input(), Prompt, 1). --spec scan_erl_exprs(device(), prompt()) -> erl_scan:tokens_result(). +-spec scan_erl_exprs(device(), prompt()) -> erl_scan:tokens_result() | request_error(). scan_erl_exprs(Io, Prompt) -> scan_erl_exprs(Io, Prompt, 1). --spec scan_erl_exprs(device(), prompt(), line()) -> erl_scan:tokens_result(). +-spec scan_erl_exprs(device(), prompt(), line()) -> erl_scan:tokens_result() | request_error(). scan_erl_exprs(Io, Prompt, Pos0) -> request(Io, {get_until,unicode,Prompt,erl_scan,tokens,[Pos0]}). --spec scan_erl_form(prompt()) -> erl_scan:tokens_result(). +-spec scan_erl_form(prompt()) -> erl_scan:tokens_result() | request_error(). scan_erl_form(Prompt) -> scan_erl_form(default_input(), Prompt, 1). --spec scan_erl_form(device(), prompt()) -> erl_scan:tokens_result(). +-spec scan_erl_form(device(), prompt()) -> erl_scan:tokens_result() | request_error(). scan_erl_form(Io, Prompt) -> scan_erl_form(Io, Prompt, 1). --spec scan_erl_form(device(), prompt(), line()) -> erl_scan:tokens_result(). +-spec scan_erl_form(device(), prompt(), line()) -> erl_scan:tokens_result() | request_error(). scan_erl_form(Io, Prompt, Pos0) -> request(Io, {get_until,unicode,Prompt,erl_scan,tokens,[Pos0]}). @@ -335,7 +323,8 @@ scan_erl_form(Io, Prompt, Pos0) -> -type parse_ret() :: {'ok', erl_parse_expr_list(), line()} | {'eof', line()} - | {'error', erl_scan:error_info(), line()}. + | {'error', erl_scan:error_info(), line()} + | request_error(). -spec parse_erl_exprs(prompt()) -> parse_ret(). @@ -364,7 +353,8 @@ parse_erl_exprs(Io, Prompt, Pos0) -> -type parse_form_ret() :: {'ok', erl_parse_absform(), line()} | {'eof', line()} - | {'error', erl_scan:error_info(), line()}. + | {'error', erl_scan:error_info(), line()} + | request_error(). -spec parse_erl_form(prompt()) -> parse_form_ret(). diff --git a/lib/stdlib/src/re.erl b/lib/stdlib/src/re.erl index 296a6b3d23..9642de17b4 100644 --- a/lib/stdlib/src/re.erl +++ b/lib/stdlib/src/re.erl @@ -208,29 +208,25 @@ replace(Subject,RE,Replacement,Options) -> process_repl_params(Options,iodata,false), FlatSubject = to_binary(Subject, Unicode), FlatReplacement = to_binary(Replacement, Unicode), - case do_replace(FlatSubject,Subject,RE,FlatReplacement,NewOpt) of - {error,_Err} -> - throw(badre); - IoList -> - case Convert of - iodata -> - IoList; - binary -> - case Unicode of - false -> - iolist_to_binary(IoList); - true -> - unicode:characters_to_binary(IoList,unicode) - end; - list -> - case Unicode of - false -> - binary_to_list(iolist_to_binary(IoList)); - true -> - unicode:characters_to_list(IoList,unicode) - end - end - end + IoList = do_replace(FlatSubject,Subject,RE,FlatReplacement,NewOpt), + case Convert of + iodata -> + IoList; + binary -> + case Unicode of + false -> + iolist_to_binary(IoList); + true -> + unicode:characters_to_binary(IoList,unicode) + end; + list -> + case Unicode of + false -> + binary_to_list(iolist_to_binary(IoList)); + true -> + unicode:characters_to_list(IoList,unicode) + end + end catch throw:badopt -> erlang:error(badarg,[Subject,RE,Replacement,Options]); diff --git a/lib/stdlib/src/supervisor.erl b/lib/stdlib/src/supervisor.erl index 7102fb9f6e..3c5800effa 100644 --- a/lib/stdlib/src/supervisor.erl +++ b/lib/stdlib/src/supervisor.erl @@ -1,7 +1,7 @@ %% %% %CopyrightBegin% %% -%% Copyright Ericsson AB 1996-2010. All Rights Reserved. +%% Copyright Ericsson AB 1996-2011. All Rights Reserved. %% %% The contents of this file are subject to the Erlang Public License, %% Version 1.1, (the "License"); you may not use this file except in @@ -40,7 +40,7 @@ %%-------------------------------------------------------------------------- -type child_id() :: pid() | 'undefined'. --type mfargs() :: {module(), atom(), [term()]}. +-type mfargs() :: {module(), atom(), [term()] | undefined}. -type modules() :: [module()] | 'dynamic'. -type restart() :: 'permanent' | 'transient' | 'temporary'. -type shutdown() :: 'brutal_kill' | timeout(). @@ -69,7 +69,7 @@ -record(state, {name, strategy :: strategy(), children = [] :: [child()], - dynamics = ?DICT:new() :: ?DICT(), + dynamics :: ?DICT() | list(), intensity :: non_neg_integer(), period :: pos_integer(), restarts = [], @@ -283,16 +283,15 @@ do_start_child_i(M, F, A) -> -spec handle_call(call(), term(), state()) -> {'reply', term(), state()}. handle_call({start_child, EArgs}, _From, State) when ?is_simple(State) -> - #child{mfargs = {M, F, A}} = hd(State#state.children), + Child = hd(State#state.children), + #child{mfargs = {M, F, A}} = Child, Args = A ++ EArgs, case do_start_child_i(M, F, Args) of {ok, Pid} -> - NState = State#state{dynamics = - ?DICT:store(Pid, Args, State#state.dynamics)}, + NState = save_dynamic_child(Child#child.restart_type, Pid, Args, State), {reply, {ok, Pid}, NState}; {ok, Pid, Extra} -> - NState = State#state{dynamics = - ?DICT:store(Pid, Args, State#state.dynamics)}, + NState = save_dynamic_child(Child#child.restart_type, Pid, Args, State), {reply, {ok, Pid, Extra}, NState}; What -> {reply, What, State} @@ -351,10 +350,20 @@ handle_call({terminate_child, Name}, _From, State) -> {reply, {error, not_found}, State} end; -handle_call(which_children, _From, State) when ?is_simple(State) -> - [#child{child_type = CT, modules = Mods}] = State#state.children, +handle_call(which_children, _From, #state{children = [#child{restart_type = temporary, + child_type = CT, + modules = Mods}]} = + State) when ?is_simple(State) -> + Reply = lists:map(fun(Pid) -> {undefined, Pid, CT, Mods} end, dynamics_db(temporary, + State#state.dynamics)), + {reply, Reply, State}; + +handle_call(which_children, _From, #state{children = [#child{restart_type = RType, + child_type = CT, + modules = Mods}]} = + State) when ?is_simple(State) -> Reply = lists:map(fun({Pid, _}) -> {undefined, Pid, CT, Mods} end, - ?DICT:to_list(State#state.dynamics)), + ?DICT:to_list(dynamics_db(RType, State#state.dynamics))), {reply, Reply, State}; handle_call(which_children, _From, State) -> @@ -366,13 +375,31 @@ handle_call(which_children, _From, State) -> State#state.children), {reply, Resp, State}; -handle_call(count_children, _From, State) when ?is_simple(State) -> - [#child{child_type = CT}] = State#state.children, + +handle_call(count_children, _From, #state{children = [#child{restart_type = temporary, + child_type = CT}]} = State) + when ?is_simple(State) -> + {Active, Count} = + lists:foldl(fun(Pid, {Alive, Tot}) -> + if is_pid(Pid) -> {Alive+1, Tot +1}; + true -> {Alive, Tot + 1} end + end, {0, 0}, dynamics_db(temporary, State#state.dynamics)), + Reply = case CT of + supervisor -> [{specs, 1}, {active, Active}, + {supervisors, Count}, {workers, 0}]; + worker -> [{specs, 1}, {active, Active}, + {supervisors, 0}, {workers, Count}] + end, + {reply, Reply, State}; + +handle_call(count_children, _From, #state{children = [#child{restart_type = RType, + child_type = CT}]} = State) + when ?is_simple(State) -> {Active, Count} = ?DICT:fold(fun(Pid, _Val, {Alive, Tot}) -> if is_pid(Pid) -> {Alive+1, Tot +1}; true -> {Alive, Tot + 1} end - end, {0, 0}, State#state.dynamics), + end, {0, 0}, dynamics_db(RType, State#state.dynamics)), Reply = case CT of supervisor -> [{specs, 1}, {active, Active}, {supervisors, Count}, {workers, 0}]; @@ -535,15 +562,11 @@ handle_start_child(Child, State) -> false -> case do_start_child(State#state.name, Child) of {ok, Pid} -> - Children = State#state.children, {{ok, Pid}, - State#state{children = - [Child#child{pid = Pid}|Children]}}; + save_child(Child#child{pid = Pid}, State)}; {ok, Pid, Extra} -> - Children = State#state.children, {{ok, Pid, Extra}, - State#state{children = - [Child#child{pid = Pid}|Children]}}; + save_child(Child#child{pid = Pid}, State)}; {error, What} -> {{error, {What, Child}}, State} end; @@ -558,22 +581,21 @@ handle_start_child(Child, State) -> %%% Returns: {ok, state()} | {shutdown, state()} %%% --------------------------------------------------- -restart_child(Pid, Reason, State) when ?is_simple(State) -> - case ?DICT:find(Pid, State#state.dynamics) of +restart_child(Pid, Reason, #state{children = [Child]} = State) when ?is_simple(State) -> + RestartType = Child#child.restart_type, + case dynamic_child_args(Pid, dynamics_db(RestartType, State#state.dynamics)) of {ok, Args} -> - [Child] = State#state.children, - RestartType = Child#child.restart_type, {M, F, _} = Child#child.mfargs, NChild = Child#child{pid = Pid, mfargs = {M, F, Args}}, do_restart(RestartType, Reason, NChild, State); error -> - {ok, State} + {ok, State} end; + restart_child(Pid, Reason, State) -> Children = State#state.children, case lists:keyfind(Pid, #child.pid, Children) of - #child{} = Child -> - RestartType = Child#child.restart_type, + #child{restart_type = RestartType} = Child -> do_restart(RestartType, Reason, Child, State); false -> {ok, State} @@ -608,7 +630,8 @@ restart(Child, State) -> restart(simple_one_for_one, Child, State) -> #child{mfargs = {M, F, A}} = Child, - Dynamics = ?DICT:erase(Child#child.pid, State#state.dynamics), + Dynamics = ?DICT:erase(Child#child.pid, dynamics_db(Child#child.restart_type, + State#state.dynamics)), case do_start_child_i(M, F, A) of {ok, Pid} -> NState = State#state{dynamics = ?DICT:store(Pid, A, Dynamics)}, @@ -755,8 +778,40 @@ monitor_child(Pid) -> %%----------------------------------------------------------------- %% Child/State manipulating functions. %%----------------------------------------------------------------- -state_del_child(#child{pid = Pid}, State) when ?is_simple(State) -> - NDynamics = ?DICT:erase(Pid, State#state.dynamics), + +%% Note we do not want to save the parameter list for temporary processes as +%% they will not be restarted, and hence we do not need this information. +%% Especially for dynamic children to simple_one_for_one supervisors +%% it could become very costly as it is not uncommon to spawn +%% very many such processes. +save_child(#child{restart_type = temporary, + mfargs = {M, F, _}} = Child, #state{children = Children} = State) -> + State#state{children = [Child#child{mfargs = {M, F, undefined}} |Children]}; +save_child(Child, #state{children = Children} = State) -> + State#state{children = [Child |Children]}. + +save_dynamic_child(temporary, Pid, _, #state{dynamics = Dynamics} = State) -> + State#state{dynamics = [Pid | dynamics_db(temporary, Dynamics)]}; +save_dynamic_child(RestartType, Pid, Args, #state{dynamics = Dynamics} = State) -> + State#state{dynamics = ?DICT:store(Pid, Args, dynamics_db(RestartType, Dynamics))}. + +dynamics_db(temporary, undefined) -> + []; +dynamics_db(_, undefined) -> + ?DICT:new(); +dynamics_db(_,Dynamics) -> + Dynamics. + +dynamic_child_args(_, Dynamics) when is_list(Dynamics)-> + {ok, undefined}; +dynamic_child_args(Pid, Dynamics) -> + ?DICT:find(Pid, Dynamics). + +state_del_child(#child{pid = Pid, restart_type = temporary}, State) when ?is_simple(State) -> + NDynamics = lists:delete(Pid, dynamics_db(temporary, State#state.dynamics)), + State#state{dynamics = NDynamics}; +state_del_child(#child{pid = Pid, restart_type = RType}, State) when ?is_simple(State) -> + NDynamics = ?DICT:erase(Pid, dynamics_db(RType, State#state.dynamics)), State#state{dynamics = NDynamics}; state_del_child(Child, State) -> NChildren = del_child(Child#child.name, State#state.children), |