]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/ocaml/contrib/otherlibs/unix/unixsupport.c
Update
[l4.git] / l4 / pkg / ocaml / ocaml / contrib / otherlibs / unix / unixsupport.c
1 /***********************************************************************/
2 /*                                                                     */
3 /*                           Objective Caml                            */
4 /*                                                                     */
5 /*            Xavier Leroy, projet Cristal, INRIA Rocquencourt         */
6 /*                                                                     */
7 /*  Copyright 1996 Institut National de Recherche en Informatique et   */
8 /*  en Automatique.  All rights reserved.  This file is distributed    */
9 /*  under the terms of the GNU Library General Public License, with    */
10 /*  the special exception on linking described in file ../../LICENSE.  */
11 /*                                                                     */
12 /***********************************************************************/
13
14 /* $Id: unixsupport.c 7045 2005-09-06 12:38:32Z doligez $ */
15
16 #include <mlvalues.h>
17 #include <alloc.h>
18 #include <callback.h>
19 #include <memory.h>
20 #include <fail.h>
21 #include "unixsupport.h"
22 #include "cst2constr.h"
23 #include <errno.h>
24
25 #ifndef E2BIG
26 #define E2BIG (-1)
27 #endif
28 #ifndef EACCES
29 #define EACCES (-1)
30 #endif
31 #ifndef EAGAIN
32 #define EAGAIN (-1)
33 #endif
34 #ifndef EBADF
35 #define EBADF (-1)
36 #endif
37 #ifndef EBUSY
38 #define EBUSY (-1)
39 #endif
40 #ifndef ECHILD
41 #define ECHILD (-1)
42 #endif
43 #ifndef EDEADLK
44 #define EDEADLK (-1)
45 #endif
46 #ifndef EDOM
47 #define EDOM (-1)
48 #endif
49 #ifndef EEXIST
50 #define EEXIST (-1)
51 #endif
52
53 #ifndef EFAULT
54 #define EFAULT (-1)
55 #endif
56 #ifndef EFBIG
57 #define EFBIG (-1)
58 #endif
59 #ifndef EINTR
60 #define EINTR (-1)
61 #endif
62 #ifndef EINVAL
63 #define EINVAL (-1)
64 #endif
65 #ifndef EIO
66 #define EIO (-1)
67 #endif
68 #ifndef EISDIR
69 #define EISDIR (-1)
70 #endif
71 #ifndef EMFILE
72 #define EMFILE (-1)
73 #endif
74 #ifndef EMLINK
75 #define EMLINK (-1)
76 #endif
77 #ifndef ENAMETOOLONG
78 #define ENAMETOOLONG (-1)
79 #endif
80 #ifndef ENFILE
81 #define ENFILE (-1)
82 #endif
83 #ifndef ENODEV
84 #define ENODEV (-1)
85 #endif
86 #ifndef ENOENT
87 #define ENOENT (-1)
88 #endif
89 #ifndef ENOEXEC
90 #define ENOEXEC (-1)
91 #endif
92 #ifndef ENOLCK
93 #define ENOLCK (-1)
94 #endif
95 #ifndef ENOMEM
96 #define ENOMEM (-1)
97 #endif
98 #ifndef ENOSPC
99 #define ENOSPC (-1)
100 #endif
101 #ifndef ENOSYS
102 #define ENOSYS (-1)
103 #endif
104 #ifndef ENOTDIR
105 #define ENOTDIR (-1)
106 #endif
107 #ifndef ENOTEMPTY
108 #define ENOTEMPTY (-1)
109 #endif
110 #ifndef ENOTTY
111 #define ENOTTY (-1)
112 #endif
113 #ifndef ENXIO
114 #define ENXIO (-1)
115 #endif
116 #ifndef EPERM
117 #define EPERM (-1)
118 #endif
119 #ifndef EPIPE
120 #define EPIPE (-1)
121 #endif
122 #ifndef ERANGE
123 #define ERANGE (-1)
124 #endif
125 #ifndef EROFS
126 #define EROFS (-1)
127 #endif
128 #ifndef ESPIPE
129 #define ESPIPE (-1)
130 #endif
131 #ifndef ESRCH
132 #define ESRCH (-1)
133 #endif
134 #ifndef EXDEV
135 #define EXDEV (-1)
136 #endif
137 #ifndef EWOULDBLOCK
138 #define EWOULDBLOCK (-1)
139 #endif
140 #ifndef EINPROGRESS
141 #define EINPROGRESS (-1)
142 #endif
143 #ifndef EALREADY
144 #define EALREADY (-1)
145 #endif
146 #ifndef ENOTSOCK
147 #define ENOTSOCK (-1)
148 #endif
149 #ifndef EDESTADDRREQ
150 #define EDESTADDRREQ (-1)
151 #endif
152 #ifndef EMSGSIZE
153 #define EMSGSIZE (-1)
154 #endif
155 #ifndef EPROTOTYPE
156 #define EPROTOTYPE (-1)
157 #endif
158 #ifndef ENOPROTOOPT
159 #define ENOPROTOOPT (-1)
160 #endif
161 #ifndef EPROTONOSUPPORT
162 #define EPROTONOSUPPORT (-1)
163 #endif
164 #ifndef ESOCKTNOSUPPORT
165 #define ESOCKTNOSUPPORT (-1)
166 #endif
167 #ifndef EOPNOTSUPP
168 #define EOPNOTSUPP (-1)
169 #endif
170 #ifndef EPFNOSUPPORT
171 #define EPFNOSUPPORT (-1)
172 #endif
173 #ifndef EAFNOSUPPORT
174 #define EAFNOSUPPORT (-1)
175 #endif
176 #ifndef EADDRINUSE
177 #define EADDRINUSE (-1)
178 #endif
179 #ifndef EADDRNOTAVAIL
180 #define EADDRNOTAVAIL (-1)
181 #endif
182 #ifndef ENETDOWN
183 #define ENETDOWN (-1)
184 #endif
185 #ifndef ENETUNREACH
186 #define ENETUNREACH (-1)
187 #endif
188 #ifndef ENETRESET
189 #define ENETRESET (-1)
190 #endif
191 #ifndef ECONNABORTED
192 #define ECONNABORTED (-1)
193 #endif
194 #ifndef ECONNRESET
195 #define ECONNRESET (-1)
196 #endif
197 #ifndef ENOBUFS
198 #define ENOBUFS (-1)
199 #endif
200 #ifndef EISCONN
201 #define EISCONN (-1)
202 #endif
203 #ifndef ENOTCONN
204 #define ENOTCONN (-1)
205 #endif
206 #ifndef ESHUTDOWN
207 #define ESHUTDOWN (-1)
208 #endif
209 #ifndef ETOOMANYREFS
210 #define ETOOMANYREFS (-1)
211 #endif
212 #ifndef ETIMEDOUT
213 #define ETIMEDOUT (-1)
214 #endif
215 #ifndef ECONNREFUSED
216 #define ECONNREFUSED (-1)
217 #endif
218 #ifndef EHOSTDOWN
219 #define EHOSTDOWN (-1)
220 #endif
221 #ifndef EHOSTUNREACH
222 #define EHOSTUNREACH (-1)
223 #endif
224 #ifndef ENOTEMPTY
225 #define ENOTEMPTY (-1)
226 #endif
227 #ifndef ELOOP
228 #define ELOOP (-1)
229 #endif
230 #ifndef EOVERFLOW
231 #define EOVERFLOW (-1)
232 #endif
233
234 int error_table[] = {
235   E2BIG, EACCES, EAGAIN, EBADF, EBUSY, ECHILD, EDEADLK, EDOM,
236   EEXIST, EFAULT, EFBIG, EINTR, EINVAL, EIO, EISDIR, EMFILE, EMLINK,
237   ENAMETOOLONG, ENFILE, ENODEV, ENOENT, ENOEXEC, ENOLCK, ENOMEM, ENOSPC,
238   ENOSYS, ENOTDIR, ENOTEMPTY, ENOTTY, ENXIO, EPERM, EPIPE, ERANGE,
239   EROFS, ESPIPE, ESRCH, EXDEV, EWOULDBLOCK, EINPROGRESS, EALREADY,
240   ENOTSOCK, EDESTADDRREQ, EMSGSIZE, EPROTOTYPE, ENOPROTOOPT,
241   EPROTONOSUPPORT, ESOCKTNOSUPPORT, EOPNOTSUPP, EPFNOSUPPORT,
242   EAFNOSUPPORT, EADDRINUSE, EADDRNOTAVAIL, ENETDOWN, ENETUNREACH,
243   ENETRESET, ECONNABORTED, ECONNRESET, ENOBUFS, EISCONN, ENOTCONN,
244   ESHUTDOWN, ETOOMANYREFS, ETIMEDOUT, ECONNREFUSED, EHOSTDOWN,
245   EHOSTUNREACH, ELOOP, EOVERFLOW /*, EUNKNOWNERR */
246 };
247
248 static value * unix_error_exn = NULL;
249
250 value unix_error_of_code (int errcode)
251 {
252   int errconstr;
253   value err;
254
255   errconstr = 
256       cst_to_constr(errcode, error_table, sizeof(error_table)/sizeof(int), -1);
257   if (errconstr == Val_int(-1)) {
258     err = alloc_small(1, 0);
259     Field(err, 0) = Val_int(errcode);
260   } else {
261     err = errconstr;
262   }
263   return err;
264 }
265
266 void unix_error(int errcode, char *cmdname, value cmdarg)
267 {
268   value res;
269   value name = Val_unit, err = Val_unit, arg = Val_unit;
270
271   Begin_roots3 (name, err, arg);
272     arg = cmdarg == Nothing ? copy_string("") : cmdarg;
273     name = copy_string(cmdname);
274     err = unix_error_of_code (errcode);
275     if (unix_error_exn == NULL) {
276       unix_error_exn = caml_named_value("Unix.Unix_error");
277       if (unix_error_exn == NULL)
278         invalid_argument("Exception Unix.Unix_error not initialized, please link unix.cma");
279     }
280     res = alloc_small(4, 0);
281     Field(res, 0) = *unix_error_exn;
282     Field(res, 1) = err;
283     Field(res, 2) = name;
284     Field(res, 3) = arg;
285   End_roots();
286   mlraise(res);
287 }
288
289 void uerror(char *cmdname, value cmdarg)
290 {
291   unix_error(errno, cmdname, cmdarg);
292 }
293