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

« back to all changes in this revision

Viewing changes to lib/stdlib/src/erl_posix_msg.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
3
%% 
4
 
%% Copyright Ericsson AB 1997-2009. All Rights Reserved.
 
4
%% Copyright Ericsson AB 1997-2010. All Rights Reserved.
5
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
24
24
 
25
25
-spec message(atom()) -> string().
26
26
 
27
 
message(e2big) -> "argument list too long";
28
 
message(eacces) -> "permission denied";
29
 
message(eaddrinuse) -> "address already in use";
30
 
message(eaddrnotavail) -> "can't assign requested address";
31
 
message(eadv) -> "advertise error";
32
 
message(eafnosupport) -> "address family not supported by protocol family";
33
 
message(eagain) -> "resource temporarily unavailable";
34
 
message(ealign) -> "EALIGN";
35
 
message(ealready) -> "operation already in progress";
36
 
message(ebade) -> "bad exchange descriptor";
37
 
message(ebadf) -> "bad file number";
38
 
message(ebadfd) -> "file descriptor in bad state";
39
 
message(ebadmsg) -> "not a data message";
40
 
message(ebadr) -> "bad request descriptor";
41
 
message(ebadrpc) -> "RPC structure is bad";
42
 
message(ebadrqc) -> "bad request code";
43
 
message(ebadslt) -> "invalid slot";
44
 
message(ebfont) -> "bad font file format";
45
 
message(ebusy) -> "file busy";
46
 
message(echild) -> "no children";
47
 
message(echrng) -> "channel number out of range";
48
 
message(ecomm) -> "communication error on send";
49
 
message(econnaborted) -> "software caused connection abort";
50
 
message(econnrefused) -> "connection refused";
51
 
message(econnreset) -> "connection reset by peer";
52
 
message(edeadlk) -> "resource deadlock avoided";
53
 
message(edeadlock) -> "resource deadlock avoided";
54
 
message(edestaddrreq) -> "destination address required";
55
 
message(edirty) -> "mounting a dirty fs w/o force";
56
 
message(edom) -> "math argument out of range";
57
 
message(edotdot) -> "cross mount point";
58
 
message(edquot) -> "disk quota exceeded";
59
 
message(eduppkg) -> "duplicate package name";
60
 
message(eexist) -> "file already exists";
61
 
message(efault) -> "bad address in system call argument";
62
 
message(efbig) -> "file too large";
63
 
message(ehostdown) -> "host is down";
64
 
message(ehostunreach) -> "host is unreachable";
65
 
message(eidrm) -> "identifier removed";
66
 
message(einit) -> "initialization error";
67
 
message(einprogress) -> "operation now in progress";
68
 
message(eintr) -> "interrupted system call";
69
 
message(einval) -> "invalid argument";
70
 
message(eio) -> "I/O error";
71
 
message(eisconn) -> "socket is already connected";
72
 
message(eisdir) -> "illegal operation on a directory";
73
 
message(eisnam) -> "is a name file";
74
 
message(elbin) -> "ELBIN";
75
 
message(el2hlt) -> "level 2 halted";
76
 
message(el2nsync) -> "level 2 not synchronized";
77
 
message(el3hlt) -> "level 3 halted";
78
 
message(el3rst) -> "level 3 reset";
79
 
message(elibacc) -> "can not access a needed shared library";
80
 
message(elibbad) -> "accessing a corrupted shared library";
81
 
message(elibexec) -> "can not exec a shared library directly";
82
 
message(elibmax) ->
83
 
    "attempting to link in more shared libraries than system limit";
84
 
message(elibscn) -> ".lib section in a.out corrupted";
85
 
message(elnrng) -> "link number out of range";
86
 
message(eloop) -> "too many levels of symbolic links";
87
 
message(emfile) -> "too many open files";
88
 
message(emlink) -> "too many links";
89
 
message(emsgsize) -> "message too long";
90
 
message(emultihop) -> "multihop attempted";
91
 
message(enametoolong) -> "file name too long";
92
 
message(enavail) -> "not available";
93
 
message(enet) -> "ENET";
94
 
message(enetdown) -> "network is down";
95
 
message(enetreset) -> "network dropped connection on reset";
96
 
message(enetunreach) -> "network is unreachable";
97
 
message(enfile) -> "file table overflow";
98
 
message(enoano) -> "anode table overflow";
99
 
message(enobufs) -> "no buffer space available";
100
 
message(enocsi) -> "no CSI structure available";
101
 
message(enodata) -> "no data available";
102
 
message(enodev) -> "no such device";
103
 
message(enoent) -> "no such file or directory";
104
 
message(enoexec) -> "exec format error";
105
 
message(enolck) -> "no locks available";
106
 
message(enolink) -> "link has be severed";
107
 
message(enomem) -> "not enough memory";
108
 
message(enomsg) -> "no message of desired type";
109
 
message(enonet) -> "machine is not on the network";
110
 
message(enopkg) -> "package not installed";
111
 
message(enoprotoopt) -> "bad proocol option";
112
 
message(enospc) -> "no space left on device";
113
 
message(enosr) -> "out of stream resources or not a stream device";
114
 
message(enosym) -> "unresolved symbol name";
115
 
message(enosys) -> "function not implemented";
116
 
message(enotblk) -> "block device required";
117
 
message(enotconn) -> "socket is not connected";
118
 
message(enotdir) -> "not a directory";
119
 
message(enotempty) -> "directory not empty";
120
 
message(enotnam) -> "not a name file";
121
 
message(enotsock) -> "socket operation on non-socket";
122
 
message(enotsup) -> "operation not supported";
123
 
message(enotty) -> "inappropriate device for ioctl";
124
 
message(enotuniq) -> "name not unique on network";
125
 
message(enxio) -> "no such device or address";
126
 
message(eopnotsupp) -> "operation not supported on socket";
127
 
message(eperm) -> "not owner";
128
 
message(epfnosupport) -> "protocol family not supported";
129
 
message(epipe) -> "broken pipe";
130
 
message(eproclim) -> "too many processes";
131
 
message(eprocunavail) -> "bad procedure for program";
132
 
message(eprogmismatch) -> "program version wrong";
133
 
message(eprogunavail) -> "RPC program not available";
134
 
message(eproto) -> "protocol error";
135
 
message(eprotonosupport) -> "protocol not suppored";
136
 
message(eprototype) -> "protocol wrong type for socket";
137
 
message(erange) -> "math result unrepresentable";
138
 
message(erefused) -> "EREFUSED";
139
 
message(eremchg) -> "remote address changed";
140
 
message(eremdev) -> "remote device";
141
 
message(eremote) -> "pathname hit remote file system";
142
 
message(eremoteio) -> "remote i/o error";
143
 
message(eremoterelease) -> "EREMOTERELEASE";
144
 
message(erofs) -> "read-only file system";
145
 
message(erpcmismatch) -> "RPC version is wrong";
146
 
message(erremote) -> "object is remote";
147
 
message(eshutdown) -> "can't send after socket shutdown";
148
 
message(esocktnosupport) -> "socket type not supported";
149
 
message(espipe) -> "invalid seek";
150
 
message(esrch) -> "no such process";
151
 
message(esrmnt) -> "srmount error";
152
 
message(estale) -> "stale remote file handle";
153
 
message(esuccess) -> "Error 0";
154
 
message(etime) -> "timer expired";
155
 
message(etimedout) -> "connection timed out";
156
 
message(etoomanyrefs) -> "too many references: can't splice";
157
 
message(etxtbsy) -> "text file or pseudo-device busy";
158
 
message(euclean) -> "structure needs cleaning";
159
 
message(eunatch) -> "protocol driver not attached";
160
 
message(eusers) -> "too many users";
161
 
message(eversion) -> "version mismatch";
162
 
message(ewouldblock) -> "operation would block";
163
 
message(exdev) -> "cross-domain link";
164
 
message(exfull) -> "message tables full";
165
 
message(nxdomain) -> "non-existing domain";
166
 
message(_) -> "unknown POSIX error".
 
27
message(T) ->
 
28
    binary_to_list(message_1(T)).
 
29
 
 
30
message_1(e2big) -> <<"argument list too long">>;
 
31
message_1(eacces) -> <<"permission denied">>;
 
32
message_1(eaddrinuse) -> <<"address already in use">>;
 
33
message_1(eaddrnotavail) -> <<"can't assign requested address">>;
 
34
message_1(eadv) -> <<"advertise error">>;
 
35
message_1(eafnosupport) -> <<"address family not supported by protocol family">>;
 
36
message_1(eagain) -> <<"resource temporarily unavailable">>;
 
37
message_1(ealign) -> <<"EALIGN">>;
 
38
message_1(ealready) -> <<"operation already in progress">>;
 
39
message_1(ebade) -> <<"bad exchange descriptor">>;
 
40
message_1(ebadf) -> <<"bad file number">>;
 
41
message_1(ebadfd) -> <<"file descriptor in bad state">>;
 
42
message_1(ebadmsg) -> <<"not a data message">>;
 
43
message_1(ebadr) -> <<"bad request descriptor">>;
 
44
message_1(ebadrpc) -> <<"RPC structure is bad">>;
 
45
message_1(ebadrqc) -> <<"bad request code">>;
 
46
message_1(ebadslt) -> <<"invalid slot">>;
 
47
message_1(ebfont) -> <<"bad font file format">>;
 
48
message_1(ebusy) -> <<"file busy">>;
 
49
message_1(echild) -> <<"no children">>;
 
50
message_1(echrng) -> <<"channel number out of range">>;
 
51
message_1(ecomm) -> <<"communication error on send">>;
 
52
message_1(econnaborted) -> <<"software caused connection abort">>;
 
53
message_1(econnrefused) -> <<"connection refused">>;
 
54
message_1(econnreset) -> <<"connection reset by peer">>;
 
55
message_1(edeadlk) -> <<"resource deadlock avoided">>;
 
56
message_1(edeadlock) -> <<"resource deadlock avoided">>;
 
57
message_1(edestaddrreq) -> <<"destination address required">>;
 
58
message_1(edirty) -> <<"mounting a dirty fs w/o force">>;
 
59
message_1(edom) -> <<"math argument out of range">>;
 
60
message_1(edotdot) -> <<"cross mount point">>;
 
61
message_1(edquot) -> <<"disk quota exceeded">>;
 
62
message_1(eduppkg) -> <<"duplicate package name">>;
 
63
message_1(eexist) -> <<"file already exists">>;
 
64
message_1(efault) -> <<"bad address in system call argument">>;
 
65
message_1(efbig) -> <<"file too large">>;
 
66
message_1(ehostdown) -> <<"host is down">>;
 
67
message_1(ehostunreach) -> <<"host is unreachable">>;
 
68
message_1(eidrm) -> <<"identifier removed">>;
 
69
message_1(einit) -> <<"initialization error">>;
 
70
message_1(einprogress) -> <<"operation now in progress">>;
 
71
message_1(eintr) -> <<"interrupted system call">>;
 
72
message_1(einval) -> <<"invalid argument">>;
 
73
message_1(eio) -> <<"I/O error">>;
 
74
message_1(eisconn) -> <<"socket is already connected">>;
 
75
message_1(eisdir) -> <<"illegal operation on a directory">>;
 
76
message_1(eisnam) -> <<"is a name file">>;
 
77
message_1(elbin) -> <<"ELBIN">>;
 
78
message_1(el2hlt) -> <<"level 2 halted">>;
 
79
message_1(el2nsync) -> <<"level 2 not synchronized">>;
 
80
message_1(el3hlt) -> <<"level 3 halted">>;
 
81
message_1(el3rst) -> <<"level 3 reset">>;
 
82
message_1(elibacc) -> <<"can not access a needed shared library">>;
 
83
message_1(elibbad) -> <<"accessing a corrupted shared library">>;
 
84
message_1(elibexec) -> <<"can not exec a shared library directly">>;
 
85
message_1(elibmax) ->
 
86
    <<"attempting to link in more shared libraries than system limit">>;
 
87
message_1(elibscn) -> <<".lib section in a.out corrupted">>;
 
88
message_1(elnrng) -> <<"link number out of range">>;
 
89
message_1(eloop) -> <<"too many levels of symbolic links">>;
 
90
message_1(emfile) -> <<"too many open files">>;
 
91
message_1(emlink) -> <<"too many links">>;
 
92
message_1(emsgsize) -> <<"message too long">>;
 
93
message_1(emultihop) -> <<"multihop attempted">>;
 
94
message_1(enametoolong) -> <<"file name too long">>;
 
95
message_1(enavail) -> <<"not available">>;
 
96
message_1(enet) -> <<"ENET">>;
 
97
message_1(enetdown) -> <<"network is down">>;
 
98
message_1(enetreset) -> <<"network dropped connection on reset">>;
 
99
message_1(enetunreach) -> <<"network is unreachable">>;
 
100
message_1(enfile) -> <<"file table overflow">>;
 
101
message_1(enoano) -> <<"anode table overflow">>;
 
102
message_1(enobufs) -> <<"no buffer space available">>;
 
103
message_1(enocsi) -> <<"no CSI structure available">>;
 
104
message_1(enodata) -> <<"no data available">>;
 
105
message_1(enodev) -> <<"no such device">>;
 
106
message_1(enoent) -> <<"no such file or directory">>;
 
107
message_1(enoexec) -> <<"exec format error">>;
 
108
message_1(enolck) -> <<"no locks available">>;
 
109
message_1(enolink) -> <<"link has be severed">>;
 
110
message_1(enomem) -> <<"not enough memory">>;
 
111
message_1(enomsg) -> <<"no message of desired type">>;
 
112
message_1(enonet) -> <<"machine is not on the network">>;
 
113
message_1(enopkg) -> <<"package not installed">>;
 
114
message_1(enoprotoopt) -> <<"bad proocol option">>;
 
115
message_1(enospc) -> <<"no space left on device">>;
 
116
message_1(enosr) -> <<"out of stream resources or not a stream device">>;
 
117
message_1(enosym) -> <<"unresolved symbol name">>;
 
118
message_1(enosys) -> <<"function not implemented">>;
 
119
message_1(enotblk) -> <<"block device required">>;
 
120
message_1(enotconn) -> <<"socket is not connected">>;
 
121
message_1(enotdir) -> <<"not a directory">>;
 
122
message_1(enotempty) -> <<"directory not empty">>;
 
123
message_1(enotnam) -> <<"not a name file">>;
 
124
message_1(enotsock) -> <<"socket operation on non-socket">>;
 
125
message_1(enotsup) -> <<"operation not supported">>;
 
126
message_1(enotty) -> <<"inappropriate device for ioctl">>;
 
127
message_1(enotuniq) -> <<"name not unique on network">>;
 
128
message_1(enxio) -> <<"no such device or address">>;
 
129
message_1(eopnotsupp) -> <<"operation not supported on socket">>;
 
130
message_1(eperm) -> <<"not owner">>;
 
131
message_1(epfnosupport) -> <<"protocol family not supported">>;
 
132
message_1(epipe) -> <<"broken pipe">>;
 
133
message_1(eproclim) -> <<"too many processes">>;
 
134
message_1(eprocunavail) -> <<"bad procedure for program">>;
 
135
message_1(eprogmismatch) -> <<"program version wrong">>;
 
136
message_1(eprogunavail) -> <<"RPC program not available">>;
 
137
message_1(eproto) -> <<"protocol error">>;
 
138
message_1(eprotonosupport) -> <<"protocol not suppored">>;
 
139
message_1(eprototype) -> <<"protocol wrong type for socket">>;
 
140
message_1(erange) -> <<"math result unrepresentable">>;
 
141
message_1(erefused) -> <<"EREFUSED">>;
 
142
message_1(eremchg) -> <<"remote address changed">>;
 
143
message_1(eremdev) -> <<"remote device">>;
 
144
message_1(eremote) -> <<"pathname hit remote file system">>;
 
145
message_1(eremoteio) -> <<"remote i/o error">>;
 
146
message_1(eremoterelease) -> <<"EREMOTERELEASE">>;
 
147
message_1(erofs) -> <<"read-only file system">>;
 
148
message_1(erpcmismatch) -> <<"RPC version is wrong">>;
 
149
message_1(erremote) -> <<"object is remote">>;
 
150
message_1(eshutdown) -> <<"can't send after socket shutdown">>;
 
151
message_1(esocktnosupport) -> <<"socket type not supported">>;
 
152
message_1(espipe) -> <<"invalid seek">>;
 
153
message_1(esrch) -> <<"no such process">>;
 
154
message_1(esrmnt) -> <<"srmount error">>;
 
155
message_1(estale) -> <<"stale remote file handle">>;
 
156
message_1(esuccess) -> <<"Error 0">>;
 
157
message_1(etime) -> <<"timer expired">>;
 
158
message_1(etimedout) -> <<"connection timed out">>;
 
159
message_1(etoomanyrefs) -> <<"too many references: can't splice">>;
 
160
message_1(etxtbsy) -> <<"text file or pseudo-device busy">>;
 
161
message_1(euclean) -> <<"structure needs cleaning">>;
 
162
message_1(eunatch) -> <<"protocol driver not attached">>;
 
163
message_1(eusers) -> <<"too many users">>;
 
164
message_1(eversion) -> <<"version mismatch">>;
 
165
message_1(ewouldblock) -> <<"operation would block">>;
 
166
message_1(exdev) -> <<"cross-domain link">>;
 
167
message_1(exfull) -> <<"message tables full">>;
 
168
message_1(nxdomain) -> <<"non-existing domain">>;
 
169
message_1(_) -> <<"unknown POSIX error">>.