diff options
-rw-r--r-- | otherlibs/graph/events.c | 4 | ||||
-rw-r--r-- | otherlibs/unix/cst2constr.c | 4 | ||||
-rw-r--r-- | otherlibs/unix/errmsg.c | 4 | ||||
-rw-r--r-- | otherlibs/unix/getgr.c | 4 | ||||
-rw-r--r-- | otherlibs/unix/gethost.c | 6 | ||||
-rw-r--r-- | otherlibs/unix/getproto.c | 4 | ||||
-rw-r--r-- | otherlibs/unix/getpw.c | 4 | ||||
-rw-r--r-- | otherlibs/unix/getserv.c | 4 | ||||
-rw-r--r-- | otherlibs/unix/lockf.c | 6 | ||||
-rw-r--r-- | otherlibs/unix/lseek.c | 2 | ||||
-rw-r--r-- | otherlibs/unix/readdir.c | 2 | ||||
-rw-r--r-- | otherlibs/unix/rename.c | 2 | ||||
-rw-r--r-- | otherlibs/unix/rewinddir.c | 2 | ||||
-rw-r--r-- | otherlibs/unix/rmdir.c | 2 | ||||
-rw-r--r-- | otherlibs/unix/select.c | 6 | ||||
-rw-r--r-- | otherlibs/unix/shutdown.c | 2 | ||||
-rw-r--r-- | otherlibs/unix/socket.c | 4 | ||||
-rw-r--r-- | otherlibs/unix/socketpair.c | 4 | ||||
-rw-r--r-- | otherlibs/unix/termios.c | 8 |
19 files changed, 37 insertions, 37 deletions
diff --git a/otherlibs/graph/events.c b/otherlibs/graph/events.c index 78f061839..17d841b3c 100644 --- a/otherlibs/graph/events.c +++ b/otherlibs/graph/events.c @@ -33,8 +33,8 @@ value gr_wait_event(eventlist) mask = 0; poll = False; - while (Tag_val(eventlist) == 1) { - switch (Tag_val(Field(eventlist, 0))) { + while (eventlist != Val_int(0)) { + switch (Int_val(Field(eventlist, 0))) { case 0: /* Button_down */ mask |= ButtonPressMask; break; case 1: /* Button_up */ diff --git a/otherlibs/unix/cst2constr.c b/otherlibs/unix/cst2constr.c index 7a519a750..7a0bb95ad 100644 --- a/otherlibs/unix/cst2constr.c +++ b/otherlibs/unix/cst2constr.c @@ -10,6 +10,6 @@ value cst_to_constr(n, tbl, size, deflt) { int i; for (i = 0; i < size; i++) - if (n == tbl[i]) return Atom(i); - return Atom(deflt); + if (n == tbl[i]) return Val_int(i); + return Val_int(deflt); } diff --git a/otherlibs/unix/errmsg.c b/otherlibs/unix/errmsg.c index d3efc8414..2da459913 100644 --- a/otherlibs/unix/errmsg.c +++ b/otherlibs/unix/errmsg.c @@ -12,7 +12,7 @@ value unix_error_message(err) value err; { int errnum; - errnum = error_table[Tag_val(err)]; + errnum = error_table[Int_val(err)]; return copy_string(strerror(errno)); } @@ -25,7 +25,7 @@ value unix_error_message(err) value err; { int errnum; - errnum = error_table[Tag_val(err)]; + errnum = error_table[Int_val(err)]; if (errnum < 0 || errnum >= sys_nerr) { return copy_string("Unknown error"); } else { diff --git a/otherlibs/unix/getgr.c b/otherlibs/unix/getgr.c index efb55b9b5..7cec68101 100644 --- a/otherlibs/unix/getgr.c +++ b/otherlibs/unix/getgr.c @@ -29,7 +29,7 @@ value unix_getgrnam(name) /* ML */ { struct group * entry; entry = getgrnam(String_val(name)); - if (entry == NULL) mlraise(Atom(NOT_FOUND_EXN)); + if (entry == NULL) raise_not_found(); return alloc_group_entry(entry); } @@ -38,6 +38,6 @@ value unix_getgrgid(gid) /* ML */ { struct group * entry; entry = getgrgid(Int_val(gid)); - if (entry == NULL) mlraise(Atom(NOT_FOUND_EXN)); + if (entry == NULL) raise_not_found(); return alloc_group_entry(entry); } diff --git a/otherlibs/unix/gethost.c b/otherlibs/unix/gethost.c index 096b28fe5..a7dcdca36 100644 --- a/otherlibs/unix/gethost.c +++ b/otherlibs/unix/gethost.c @@ -39,7 +39,7 @@ static value alloc_host_entry(entry) res = alloc_tuple(4); Field(res, 0) = r[0]; Field(res, 1) = r[1]; - Field(res, 2) = entry->h_addrtype == PF_UNIX ? Atom(0) : Atom(1); + Field(res, 2) = entry->h_addrtype == PF_UNIX ? Val_int(0) : Val_int(1); Field(res, 3) = r[2]; Pop_roots(); return res; @@ -52,7 +52,7 @@ value unix_gethostbyaddr(a) /* ML */ struct hostent * entry; in_addr.s_addr = GET_INET_ADDR(a); entry = gethostbyaddr((char *) &in_addr, sizeof(in_addr), 0); - if (entry == (struct hostent *) NULL) mlraise(Atom(NOT_FOUND_EXN)); + if (entry == (struct hostent *) NULL) raise_not_found(); return alloc_host_entry(entry); } @@ -61,7 +61,7 @@ value unix_gethostbyname(name) /* ML */ { struct hostent * entry; entry = gethostbyname(String_val(name)); - if (entry == (struct hostent *) NULL) mlraise(Atom(NOT_FOUND_EXN)); + if (entry == (struct hostent *) NULL) raise_not_found(); return alloc_host_entry(entry); } diff --git a/otherlibs/unix/getproto.c b/otherlibs/unix/getproto.c index 56ea69913..aed732de0 100644 --- a/otherlibs/unix/getproto.c +++ b/otherlibs/unix/getproto.c @@ -29,7 +29,7 @@ value unix_getprotobyname(name) /* ML */ { struct protoent * entry; entry = getprotobyname(String_val(name)); - if (entry == (struct protoent *) NULL) mlraise(Atom(NOT_FOUND_EXN)); + if (entry == (struct protoent *) NULL) raise_not_found(); return alloc_proto_entry(entry); } @@ -38,7 +38,7 @@ value unix_getprotobynumber(proto) /* ML */ { struct protoent * entry; entry = getprotobynumber(Int_val(proto)); - if (entry == (struct protoent *) NULL) mlraise(Atom(NOT_FOUND_EXN)); + if (entry == (struct protoent *) NULL) raise_not_found(); return alloc_proto_entry(entry); } diff --git a/otherlibs/unix/getpw.c b/otherlibs/unix/getpw.c index 86d27474a..6a00f0fe9 100644 --- a/otherlibs/unix/getpw.c +++ b/otherlibs/unix/getpw.c @@ -33,7 +33,7 @@ value unix_getpwnam(name) /* ML */ { struct passwd * entry; entry = getpwnam(String_val(name)); - if (entry == (struct passwd *) NULL) mlraise(Atom(NOT_FOUND_EXN)); + if (entry == (struct passwd *) NULL) raise_not_found(); return alloc_passwd_entry(entry); } @@ -42,6 +42,6 @@ value unix_getpwuid(uid) /* ML */ { struct passwd * entry; entry = getpwuid(Int_val(uid)); - if (entry == (struct passwd *) NULL) mlraise(Atom(NOT_FOUND_EXN)); + if (entry == (struct passwd *) NULL) raise_not_found(); return alloc_passwd_entry(entry); } diff --git a/otherlibs/unix/getserv.c b/otherlibs/unix/getserv.c index ddd25dafb..0d2534a61 100644 --- a/otherlibs/unix/getserv.c +++ b/otherlibs/unix/getserv.c @@ -34,7 +34,7 @@ value unix_getservbyname(name, proto) /* ML */ { struct servent * entry; entry = getservbyname(String_val(name), String_val(proto)); - if (entry == (struct servent *) NULL) mlraise(Atom(NOT_FOUND_EXN)); + if (entry == (struct servent *) NULL) raise_not_found(); return alloc_service_entry(entry); } @@ -43,7 +43,7 @@ value unix_getservbyport(port, proto) /* ML */ { struct servent * entry; entry = getservbyport(Int_val(port), String_val(proto)); - if (entry == (struct servent *) NULL) mlraise(Atom(NOT_FOUND_EXN)); + if (entry == (struct servent *) NULL) raise_not_found(); return alloc_service_entry(entry); } diff --git a/otherlibs/unix/lockf.c b/otherlibs/unix/lockf.c index bfc22c77d..d85d1d1b3 100644 --- a/otherlibs/unix/lockf.c +++ b/otherlibs/unix/lockf.c @@ -18,9 +18,9 @@ static int lock_command_table[] = { value unix_lockf(fd, cmd, span) /* ML */ value fd, cmd, span; { - if (lockf(Int_val(fd), lock_command_table[Tag_val(cmd)], Long_val(span)) + if (lockf(Int_val(fd), lock_command_table[Int_val(cmd)], Long_val(span)) == -1) uerror("lockf", Nothing); - return Atom(0); + return Val_unit; } #else @@ -48,7 +48,7 @@ value unix_lockf(fd, cmd, span) /* ML */ l.l_start = 0L; l.l_len = size; } - switch (Tag_val(cmd)) { + switch (Int_val(cmd)) { case 0: /* F_ULOCK */ l.l_type = F_UNLCK; ret = fcntl(fildes, F_SETLK, &l); diff --git a/otherlibs/unix/lseek.c b/otherlibs/unix/lseek.c index 05d6d2422..4a34787f7 100644 --- a/otherlibs/unix/lseek.c +++ b/otherlibs/unix/lseek.c @@ -18,7 +18,7 @@ value unix_lseek(fd, ofs, cmd) /* ML */ { long ret; ret = lseek(Int_val(fd), Long_val(ofs), - seek_command_table[Tag_val(cmd)]); + seek_command_table[Int_val(cmd)]); if (ret == -1) uerror("lseek", Nothing); return Val_long(ret); } diff --git a/otherlibs/unix/readdir.c b/otherlibs/unix/readdir.c index 41093f95a..c544b6e51 100644 --- a/otherlibs/unix/readdir.c +++ b/otherlibs/unix/readdir.c @@ -17,6 +17,6 @@ value unix_readdir(d) /* ML */ directory_entry * e; e = readdir((DIR *) d); - if (e == (directory_entry *) NULL) mlraise(Atom(END_OF_FILE_EXN)); + if (e == (directory_entry *) NULL) raise_end_of_file(); return copy_string(e->d_name); } diff --git a/otherlibs/unix/rename.c b/otherlibs/unix/rename.c index 76b6e3f6e..b6cc1e21d 100644 --- a/otherlibs/unix/rename.c +++ b/otherlibs/unix/rename.c @@ -6,5 +6,5 @@ value unix_rename(path1, path2) /* ML */ { if (rename(String_val(path1), String_val(path2)) == -1) uerror("rename", path1); - return Atom(0); + return Val_unit; } diff --git a/otherlibs/unix/rewinddir.c b/otherlibs/unix/rewinddir.c index 4062a46c7..9539e0923 100644 --- a/otherlibs/unix/rewinddir.c +++ b/otherlibs/unix/rewinddir.c @@ -11,5 +11,5 @@ value unix_rewinddir(d) /* ML */ value d; { rewinddir((DIR *) d); - return Atom(0); + return Val_unit; } diff --git a/otherlibs/unix/rmdir.c b/otherlibs/unix/rmdir.c index 49e82b253..dcf5a5493 100644 --- a/otherlibs/unix/rmdir.c +++ b/otherlibs/unix/rmdir.c @@ -5,5 +5,5 @@ value unix_rmdir(path) /* ML */ value path; { if (rmdir(String_val(path)) == -1) uerror("rmdir", path); - return Atom(0); + return Val_unit; } diff --git a/otherlibs/unix/select.c b/otherlibs/unix/select.c index 7015cdb75..14d063706 100644 --- a/otherlibs/unix/select.c +++ b/otherlibs/unix/select.c @@ -25,7 +25,7 @@ static void fdlist_to_fdset(fdlist, fdset) { value l; FD_ZERO(fdset); - for (l = fdlist; Tag_val(l) == 1; l = Field(l, 1)) { + for (l = fdlist; l != Val_int(0); l = Field(l, 1)) { FD_SET(Int_val(Field(l, 0)), fdset); } } @@ -36,10 +36,10 @@ static value fdset_to_fdlist(fdset) int i; Push_roots(roots, 1) #define res roots[0] - res = Atom(0); + res = Val_int(0); for (i = FD_SETSIZE - 1; i >= 0; i--) { if (FD_ISSET(i, fdset)) { - value newres = alloc(2, 1); + value newres = alloc(2, 0); Field(newres, 0) = Val_int(i); Field(newres, 1) = res; res = newres; diff --git a/otherlibs/unix/shutdown.c b/otherlibs/unix/shutdown.c index 79326494e..bd37c1e5b 100644 --- a/otherlibs/unix/shutdown.c +++ b/otherlibs/unix/shutdown.c @@ -10,7 +10,7 @@ static int shutdown_command_table[] = { value unix_shutdown(sock, cmd) /* ML */ value sock, cmd; { - if (shutdown(Int_val(sock), shutdown_command_table[Tag_val(cmd)]) == -1) + if (shutdown(Int_val(sock), shutdown_command_table[Int_val(cmd)]) == -1) uerror("shutdown", Nothing); return Val_unit; } diff --git a/otherlibs/unix/socket.c b/otherlibs/unix/socket.c index 6a1e19754..9ad189507 100644 --- a/otherlibs/unix/socket.c +++ b/otherlibs/unix/socket.c @@ -18,8 +18,8 @@ value unix_socket(domain, type, proto) /* ML */ value domain, type, proto; { int retcode; - retcode = socket(socket_domain_table[Tag_val(domain)], - socket_type_table[Tag_val(type)], + retcode = socket(socket_domain_table[Int_val(domain)], + socket_type_table[Int_val(type)], Int_val(proto)); if (retcode == -1) uerror("socket", Nothing); return Val_int(retcode); diff --git a/otherlibs/unix/socketpair.c b/otherlibs/unix/socketpair.c index 5a5a02d96..0b84dea1d 100644 --- a/otherlibs/unix/socketpair.c +++ b/otherlibs/unix/socketpair.c @@ -11,8 +11,8 @@ value unix_socketpair(domain, type, proto) /* ML */ { int sv[2]; value res; - if (socketpair(socket_domain_table[Tag_val(domain)], - socket_type_table[Tag_val(type)], + if (socketpair(socket_domain_table[Int_val(domain)], + socket_type_table[Int_val(type)], Int_val(proto), sv) == -1) uerror("socketpair", Nothing); res = alloc_tuple(2); diff --git a/otherlibs/unix/termios.c b/otherlibs/unix/termios.c index fdb0fb95d..78bf0d073 100644 --- a/otherlibs/unix/termios.c +++ b/otherlibs/unix/termios.c @@ -177,7 +177,7 @@ static void decode_terminal_status(src) case Bool: { int * dst = (int *) (*pc++); int msk = *pc++; - if (Tag_val(*src) != 0) + if (Bool_val(*src)) *dst |= msk; else *dst &= ~msk; @@ -245,7 +245,7 @@ value unix_tcsetattr(fd, when, arg) uerror("tcsetattr", Nothing); decode_terminal_status(&Field(arg, 0)); if (tcsetattr(Int_val(fd), - when_flag_table[Tag_val(when)], + when_flag_table[Int_val(when)], &terminal_status) == -1) uerror("tcsetattr", Nothing); return Val_unit; @@ -273,7 +273,7 @@ static int queue_flag_table[] = { value unix_tcflush(fd, queue) value fd, queue; { - if (tcflush(Int_val(fd), queue_flag_table[Tag_val(queue)]) == -1) + if (tcflush(Int_val(fd), queue_flag_table[Int_val(queue)]) == -1) uerror("tcflush", Nothing); return Val_unit; } @@ -285,7 +285,7 @@ static int action_flag_table[] = { value unix_tcflow(fd, action) value fd, action; { - if (tcflow(Int_val(fd), action_flag_table[Tag_val(action)]) == -1) + if (tcflow(Int_val(fd), action_flag_table[Int_val(action)]) == -1) uerror("tcflow", Nothing); return Val_unit; } |