Meilleure gestion des erreurs EUNKNOWNERROR

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@1881 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Xavier Leroy 1998-02-26 12:53:08 +00:00
parent 7c6224f2e3
commit 900fada82e
4 changed files with 19 additions and 12 deletions

View File

@ -24,7 +24,7 @@ extern char * strerror(int);
value unix_error_message(value err)
{
int errnum;
errnum = error_table[Int_val(err)];
errnum = Is_block(err) ? Int_val(Field(err, 0)) : error_table[Int_val(err)];
return copy_string(strerror(errnum));
}
@ -36,7 +36,7 @@ extern char *sys_errlist[];
value unix_error_message(value err)
{
int errnum;
errnum = error_table[Int_val(err)];
errnum = Is_block(err) ? Int_val(Field(err, 0)) : error_table[Int_val(err)];
if (errnum < 0 || errnum >= sys_nerr) {
return copy_string("Unknown error");
} else {

View File

@ -79,12 +79,12 @@ type error =
| EHOSTDOWN
| EHOSTUNREACH
| ELOOP
| EUNKNOWNERR
| EUNKNOWNERR of int
exception Unix_error of error * string * string
let _ = Callback.register_exception "Unix.Unix_error"
(Unix_error(EUNKNOWNERR, "", ""))
(Unix_error(E2BIG, "", ""))
external error_message : error -> string = "unix_error_message"

View File

@ -86,7 +86,7 @@ type error =
| EHOSTUNREACH (* No route to host *)
| ELOOP (* Too many levels of symbolic links *)
(* All other errors are mapped to EUNKNOWNERR *)
| EUNKNOWNERR (* Unknown error *)
| EUNKNOWNERR of int (* Unknown error *)
(* The type of error codes. *)

View File

@ -245,21 +245,28 @@ static value * unix_error_exn = NULL;
void unix_error(int errcode, char *cmdname, value cmdarg)
{
value res;
value name = Val_unit, arg = Val_unit;
value name = Val_unit, err = Val_unit, arg = Val_unit;
int errconstr;
Begin_roots2 (name, arg);
Begin_roots3 (name, err, arg);
arg = cmdarg == Nothing ? copy_string("") : cmdarg;
name = copy_string(cmdname);
errconstr =
cst_to_constr(errcode, error_table, sizeof(error_table)/sizeof(int), -1);
if (errconstr == -1) {
err = alloc(1, 0);
Field(err, 0) = Val_int(errcode);
} else {
err = Val_int(errconstr);
}
if (unix_error_exn == NULL) {
unix_error_exn = caml_named_value("Unix.Unix_error");
if (unix_error_exn == NULL)
invalid_argument("Exception Unix.Unix_error not initialized, please link unix.cma");
}
arg = cmdarg == Nothing ? copy_string("") : cmdarg;
name = copy_string(cmdname);
res = alloc(4, 0);
Field(res, 0) = *unix_error_exn;
Field(res, 1) =
cst_to_constr(errcode, error_table, sizeof(error_table)/sizeof(int),
sizeof(error_table)/sizeof(int));
Field(res, 1) = err;
Field(res, 2) = name;
Field(res, 3) = arg;
End_roots();