summaryrefslogtreecommitdiffstats
path: root/otherlibs/unix
diff options
context:
space:
mode:
authorDamien Doligez <damien.doligez-inria.fr>1998-10-26 19:19:32 +0000
committerDamien Doligez <damien.doligez-inria.fr>1998-10-26 19:19:32 +0000
commit3be947947e3249a9b362fc790d377e43c4108a62 (patch)
treefa0c0fbdd5b3148f926e2f7f15090f7bd7d9a44d /otherlibs/unix
parent59cb8750d21154c767d7224cd0f726b5da62d59b (diff)
nouvelles fonctions alloc/alloc_small
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@2134 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'otherlibs/unix')
-rw-r--r--otherlibs/unix/accept.c4
-rw-r--r--otherlibs/unix/getgr.c4
-rw-r--r--otherlibs/unix/gethost.c6
-rw-r--r--otherlibs/unix/getproto.c4
-rw-r--r--otherlibs/unix/getpw.c4
-rw-r--r--otherlibs/unix/getserv.c4
-rw-r--r--otherlibs/unix/gmtime.c6
-rw-r--r--otherlibs/unix/itimer.c4
-rw-r--r--otherlibs/unix/pipe.c4
-rw-r--r--otherlibs/unix/select.c6
-rw-r--r--otherlibs/unix/sendrecv.c4
-rw-r--r--otherlibs/unix/signals.c4
-rw-r--r--otherlibs/unix/socketaddr.c6
-rw-r--r--otherlibs/unix/socketpair.c4
-rw-r--r--otherlibs/unix/stat.c4
-rw-r--r--otherlibs/unix/times.c4
-rw-r--r--otherlibs/unix/unixsupport.c6
-rw-r--r--otherlibs/unix/wait.c10
18 files changed, 44 insertions, 44 deletions
diff --git a/otherlibs/unix/accept.c b/otherlibs/unix/accept.c
index 8d2c2fd5b..d41eba262 100644
--- a/otherlibs/unix/accept.c
+++ b/otherlibs/unix/accept.c
@@ -5,7 +5,7 @@
/* Xavier Leroy, projet Cristal, INRIA Rocquencourt */
/* */
/* Copyright 1996 Institut National de Recherche en Informatique et */
-/* Automatique. Distributed only by permission. */
+/* en Automatique. Distributed only by permission. */
/* */
/***********************************************************************/
@@ -34,7 +34,7 @@ value unix_accept(value sock) /* ML */
if (retcode == -1) uerror("accept", Nothing);
a = alloc_sockaddr();
Begin_root (a);
- res = alloc_tuple(2);
+ res = alloc_small(2, 0);
Field(res, 0) = Val_int(retcode);
Field(res, 1) = a;
End_roots();
diff --git a/otherlibs/unix/getgr.c b/otherlibs/unix/getgr.c
index 253d0bf6d..80e09982b 100644
--- a/otherlibs/unix/getgr.c
+++ b/otherlibs/unix/getgr.c
@@ -5,7 +5,7 @@
/* Xavier Leroy, projet Cristal, INRIA Rocquencourt */
/* */
/* Copyright 1996 Institut National de Recherche en Informatique et */
-/* Automatique. Distributed only by permission. */
+/* en Automatique. Distributed only by permission. */
/* */
/***********************************************************************/
@@ -28,7 +28,7 @@ static value alloc_group_entry(struct group *entry)
name = copy_string(entry->gr_name);
pass = copy_string(entry->gr_passwd);
mem = copy_string_array(entry->gr_mem);
- res = alloc_tuple(4);
+ res = alloc_small(4, 0);
Field(res,0) = name;
Field(res,1) = pass;
Field(res,2) = Val_int(entry->gr_gid);
diff --git a/otherlibs/unix/gethost.c b/otherlibs/unix/gethost.c
index 0a47b0f57..ef7df6c1a 100644
--- a/otherlibs/unix/gethost.c
+++ b/otherlibs/unix/gethost.c
@@ -5,7 +5,7 @@
/* Xavier Leroy, projet Cristal, INRIA Rocquencourt */
/* */
/* Copyright 1996 Institut National de Recherche en Informatique et */
-/* Automatique. Distributed only by permission. */
+/* en Automatique. Distributed only by permission. */
/* */
/***********************************************************************/
@@ -50,10 +50,10 @@ static value alloc_host_entry(struct hostent *entry)
addr_list = alloc_array(alloc_one_addr, entry->h_addr_list);
#else
adr = alloc_one_addr(entry->h_addr);
- addr_list = alloc_tuple(1);
+ addr_list = alloc_small(1, 0);
Field(addr_list, 0) = adr;
#endif
- res = alloc_tuple(4);
+ res = alloc_small(4, 0);
Field(res, 0) = name;
Field(res, 1) = aliases;
Field(res, 2) = entry->h_addrtype == PF_UNIX ? Val_int(0) : Val_int(1);
diff --git a/otherlibs/unix/getproto.c b/otherlibs/unix/getproto.c
index 5fff35d31..01045df18 100644
--- a/otherlibs/unix/getproto.c
+++ b/otherlibs/unix/getproto.c
@@ -5,7 +5,7 @@
/* Xavier Leroy, projet Cristal, INRIA Rocquencourt */
/* */
/* Copyright 1996 Institut National de Recherche en Informatique et */
-/* Automatique. Distributed only by permission. */
+/* en Automatique. Distributed only by permission. */
/* */
/***********************************************************************/
@@ -33,7 +33,7 @@ static value alloc_proto_entry(struct protoent *entry)
Begin_roots2 (name, aliases);
name = copy_string(entry->p_name);
aliases = copy_string_array(entry->p_aliases);
- res = alloc_tuple(3);
+ res = alloc_small(3, 0);
Field(res,0) = name;
Field(res,1) = aliases;
Field(res,2) = Val_int(entry->p_proto);
diff --git a/otherlibs/unix/getpw.c b/otherlibs/unix/getpw.c
index c4f3e17fa..b39e98573 100644
--- a/otherlibs/unix/getpw.c
+++ b/otherlibs/unix/getpw.c
@@ -5,7 +5,7 @@
/* Xavier Leroy, projet Cristal, INRIA Rocquencourt */
/* */
/* Copyright 1996 Institut National de Recherche en Informatique et */
-/* Automatique. Distributed only by permission. */
+/* en Automatique. Distributed only by permission. */
/* */
/***********************************************************************/
@@ -30,7 +30,7 @@ static value alloc_passwd_entry(struct passwd *entry)
gecos = copy_string(entry->pw_gecos);
dir = copy_string(entry->pw_dir);
shell = copy_string(entry->pw_shell);
- res = alloc_tuple(7);
+ res = alloc_small(7, 0);
Field(res,0) = name;
Field(res,1) = passwd;
Field(res,2) = Val_int(entry->pw_uid);
diff --git a/otherlibs/unix/getserv.c b/otherlibs/unix/getserv.c
index 998a8ac5b..6cb976ac1 100644
--- a/otherlibs/unix/getserv.c
+++ b/otherlibs/unix/getserv.c
@@ -5,7 +5,7 @@
/* Xavier Leroy, projet Cristal, INRIA Rocquencourt */
/* */
/* Copyright 1996 Institut National de Recherche en Informatique et */
-/* Automatique. Distributed only by permission. */
+/* en Automatique. Distributed only by permission. */
/* */
/***********************************************************************/
@@ -38,7 +38,7 @@ static value alloc_service_entry(struct servent *entry)
name = copy_string(entry->s_name);
aliases = copy_string_array(entry->s_aliases);
proto = copy_string(entry->s_proto);
- res = alloc_tuple(4);
+ res = alloc_small(4, 0);
Field(res,0) = name;
Field(res,1) = aliases;
Field(res,2) = Val_int(ntohs(entry->s_port));
diff --git a/otherlibs/unix/gmtime.c b/otherlibs/unix/gmtime.c
index bbab949a5..0ecf8b99b 100644
--- a/otherlibs/unix/gmtime.c
+++ b/otherlibs/unix/gmtime.c
@@ -5,7 +5,7 @@
/* Xavier Leroy, projet Cristal, INRIA Rocquencourt */
/* */
/* Copyright 1996 Institut National de Recherche en Informatique et */
-/* Automatique. Distributed only by permission. */
+/* en Automatique. Distributed only by permission. */
/* */
/***********************************************************************/
@@ -20,7 +20,7 @@
static value alloc_tm(struct tm *tm)
{
value res;
- res = alloc_tuple(9);
+ res = alloc_small(9, 0);
Field(res,0) = Val_int(tm->tm_sec);
Field(res,1) = Val_int(tm->tm_min);
Field(res,2) = Val_int(tm->tm_hour);
@@ -69,7 +69,7 @@ value unix_mktime(value t) /* ML */
clock = mktime(&tm);
tmval = alloc_tm(&tm);
clkval = copy_double((double) clock);
- res = alloc_tuple(2);
+ res = alloc_small(2, 0);
Field(res, 0) = clkval;
Field(res, 1) = tmval;
End_roots ();
diff --git a/otherlibs/unix/itimer.c b/otherlibs/unix/itimer.c
index 3141dd608..b6b2945bb 100644
--- a/otherlibs/unix/itimer.c
+++ b/otherlibs/unix/itimer.c
@@ -5,7 +5,7 @@
/* Xavier Leroy, projet Cristal, INRIA Rocquencourt */
/* */
/* Copyright 1996 Institut National de Recherche en Informatique et */
-/* Automatique. Distributed only by permission. */
+/* en Automatique. Distributed only by permission. */
/* */
/***********************************************************************/
@@ -28,7 +28,7 @@
static value unix_convert_itimer(struct itimerval *tp)
{
- value res = alloc(Double_wosize * 2, Double_array_tag);
+ value res = alloc_small(Double_wosize * 2, Double_array_tag);
Store_double_field(res, 0, Get_timeval(tp->it_interval));
Store_double_field(res, 1, Get_timeval(tp->it_value));
return res;
diff --git a/otherlibs/unix/pipe.c b/otherlibs/unix/pipe.c
index 683fa9993..4c1e97ce7 100644
--- a/otherlibs/unix/pipe.c
+++ b/otherlibs/unix/pipe.c
@@ -5,7 +5,7 @@
/* Xavier Leroy, projet Cristal, INRIA Rocquencourt */
/* */
/* Copyright 1996 Institut National de Recherche en Informatique et */
-/* Automatique. Distributed only by permission. */
+/* en Automatique. Distributed only by permission. */
/* */
/***********************************************************************/
@@ -20,7 +20,7 @@ value unix_pipe(void) /* ML */
int fd[2];
value res;
if (pipe(fd) == -1) uerror("pipe", Nothing);
- res = alloc_tuple(2);
+ res = alloc_small(2, 0);
Field(res, 0) = Val_int(fd[0]);
Field(res, 1) = Val_int(fd[1]);
return res;
diff --git a/otherlibs/unix/select.c b/otherlibs/unix/select.c
index 5cbf42ca1..9ae187ee0 100644
--- a/otherlibs/unix/select.c
+++ b/otherlibs/unix/select.c
@@ -5,7 +5,7 @@
/* Xavier Leroy, projet Cristal, INRIA Rocquencourt */
/* */
/* Copyright 1996 Institut National de Recherche en Informatique et */
-/* Automatique. Distributed only by permission. */
+/* en Automatique. Distributed only by permission. */
/* */
/***********************************************************************/
@@ -58,7 +58,7 @@ static value fdset_to_fdlist(file_descr_set *fdset)
Begin_root(res);
for (i = FD_SETSIZE - 1; i >= 0; i--) {
if (FD_ISSET(i, fdset)) {
- value newres = alloc(2, 0);
+ value newres = alloc_small(2, 0);
Field(newres, 0) = Val_int(i);
Field(newres, 1) = res;
res = newres;
@@ -97,7 +97,7 @@ value unix_select(value readfds, value writefds, value exceptfds, value timeout)
read_list = fdset_to_fdlist(&read);
write_list = fdset_to_fdlist(&write);
except_list = fdset_to_fdlist(&except);
- res = alloc_tuple(3);
+ res = alloc_small(3, 0);
Field(res, 0) = read_list;
Field(res, 1) = write_list;
Field(res, 2) = except_list;
diff --git a/otherlibs/unix/sendrecv.c b/otherlibs/unix/sendrecv.c
index 0df230dc8..a4c6386a7 100644
--- a/otherlibs/unix/sendrecv.c
+++ b/otherlibs/unix/sendrecv.c
@@ -5,7 +5,7 @@
/* Xavier Leroy, projet Cristal, INRIA Rocquencourt */
/* */
/* Copyright 1996 Institut National de Recherche en Informatique et */
-/* Automatique. Distributed only by permission. */
+/* en Automatique. Distributed only by permission. */
/* */
/***********************************************************************/
@@ -64,7 +64,7 @@ value unix_recvfrom(value sock, value buff, value ofs, value len, value flags) /
if (ret == -1) uerror("recvfrom", Nothing);
bcopy(iobuf, &Byte(buff, Long_val(ofs)), ret);
adr = alloc_sockaddr();
- res = alloc_tuple(2);
+ res = alloc_small(2, 0);
Field(res, 0) = Val_int(ret);
Field(res, 1) = adr;
End_roots();
diff --git a/otherlibs/unix/signals.c b/otherlibs/unix/signals.c
index d1d71b2eb..e5f1130b1 100644
--- a/otherlibs/unix/signals.c
+++ b/otherlibs/unix/signals.c
@@ -5,7 +5,7 @@
/* Xavier Leroy, projet Cristal, INRIA Rocquencourt */
/* */
/* Copyright 1998 Institut National de Recherche en Informatique et */
-/* Automatique. Distributed only by permission. */
+/* en Automatique. Distributed only by permission. */
/* */
/***********************************************************************/
@@ -38,7 +38,7 @@ static value encode_sigset(sigset_t * set)
Begin_root(res)
for (i = 1; i < NSIG; i++)
if (sigismember(set, i)) {
- value newcons = alloc(2, 0);
+ value newcons = alloc_small(2, 0);
Field(newcons, 0) = Val_int(i);
Field(newcons, 1) = res;
res = newcons;
diff --git a/otherlibs/unix/socketaddr.c b/otherlibs/unix/socketaddr.c
index db1fc23b0..ebadf6340 100644
--- a/otherlibs/unix/socketaddr.c
+++ b/otherlibs/unix/socketaddr.c
@@ -5,7 +5,7 @@
/* Xavier Leroy, projet Cristal, INRIA Rocquencourt */
/* */
/* Copyright 1996 Institut National de Recherche en Informatique et */
-/* Automatique. Distributed only by permission. */
+/* en Automatique. Distributed only by permission. */
/* */
/***********************************************************************/
@@ -82,7 +82,7 @@ value alloc_sockaddr(void)
case AF_UNIX:
{ value n = copy_string(sock_addr.s_unix.sun_path);
Begin_root (n);
- res = alloc(1, 0);
+ res = alloc_small(1, 0);
Field(res,0) = n;
End_roots();
break;
@@ -91,7 +91,7 @@ value alloc_sockaddr(void)
case AF_INET:
{ value a = alloc_inet_addr(sock_addr.s_inet.sin_addr.s_addr);
Begin_root (a);
- res = alloc(2, 1);
+ res = alloc_small(2, 1);
Field(res,0) = a;
Field(res,1) = Val_int(ntohs(sock_addr.s_inet.sin_port));
End_roots();
diff --git a/otherlibs/unix/socketpair.c b/otherlibs/unix/socketpair.c
index 0f325a471..2a54d4a42 100644
--- a/otherlibs/unix/socketpair.c
+++ b/otherlibs/unix/socketpair.c
@@ -5,7 +5,7 @@
/* Xavier Leroy, projet Cristal, INRIA Rocquencourt */
/* */
/* Copyright 1996 Institut National de Recherche en Informatique et */
-/* Automatique. Distributed only by permission. */
+/* en Automatique. Distributed only by permission. */
/* */
/***********************************************************************/
@@ -29,7 +29,7 @@ value unix_socketpair(value domain, value type, value proto) /* ML */
socket_type_table[Int_val(type)],
Int_val(proto), sv) == -1)
uerror("socketpair", Nothing);
- res = alloc_tuple(2);
+ res = alloc_small(2, 0);
Field(res,0) = Val_int(sv[0]);
Field(res,1) = Val_int(sv[1]);
return res;
diff --git a/otherlibs/unix/stat.c b/otherlibs/unix/stat.c
index 628bd4c1a..37e190ed4 100644
--- a/otherlibs/unix/stat.c
+++ b/otherlibs/unix/stat.c
@@ -5,7 +5,7 @@
/* Xavier Leroy, projet Cristal, INRIA Rocquencourt */
/* */
/* Copyright 1996 Institut National de Recherche en Informatique et */
-/* Automatique. Distributed only by permission. */
+/* en Automatique. Distributed only by permission. */
/* */
/***********************************************************************/
@@ -45,7 +45,7 @@ static value stat_aux(struct stat *buf)
atime = copy_double((double) buf->st_atime);
mtime = copy_double((double) buf->st_mtime);
ctime = copy_double((double) buf->st_ctime);
- v = alloc_tuple(12);
+ v = alloc_small(12, 0);
Field (v, 0) = Val_int (buf->st_dev);
Field (v, 1) = Val_int (buf->st_ino);
Field (v, 2) = cst_to_constr(buf->st_mode & S_IFMT, file_kind_table,
diff --git a/otherlibs/unix/times.c b/otherlibs/unix/times.c
index 3692bfe20..01e125031 100644
--- a/otherlibs/unix/times.c
+++ b/otherlibs/unix/times.c
@@ -5,7 +5,7 @@
/* Xavier Leroy, projet Cristal, INRIA Rocquencourt */
/* */
/* Copyright 1996 Institut National de Recherche en Informatique et */
-/* Automatique. Distributed only by permission. */
+/* en Automatique. Distributed only by permission. */
/* */
/***********************************************************************/
@@ -33,7 +33,7 @@ value unix_times(void) /* ML */
struct tms buffer;
times(&buffer);
- res = alloc(4 * Double_wosize, Double_array_tag);
+ res = alloc_small(4 * Double_wosize, Double_array_tag);
Store_double_field(res, 0, (double) buffer.tms_utime / CLK_TCK);
Store_double_field(res, 1, (double) buffer.tms_stime / CLK_TCK);
Store_double_field(res, 2, (double) buffer.tms_cutime / CLK_TCK);
diff --git a/otherlibs/unix/unixsupport.c b/otherlibs/unix/unixsupport.c
index 157ac2635..6d4bae6d7 100644
--- a/otherlibs/unix/unixsupport.c
+++ b/otherlibs/unix/unixsupport.c
@@ -5,7 +5,7 @@
/* Xavier Leroy, projet Cristal, INRIA Rocquencourt */
/* */
/* Copyright 1996 Institut National de Recherche en Informatique et */
-/* Automatique. Distributed only by permission. */
+/* en Automatique. Distributed only by permission. */
/* */
/***********************************************************************/
@@ -254,7 +254,7 @@ void unix_error(int errcode, char *cmdname, value cmdarg)
errconstr =
cst_to_constr(errcode, error_table, sizeof(error_table)/sizeof(int), -1);
if (errconstr == Val_int(-1)) {
- err = alloc(1, 0);
+ err = alloc_small(1, 0);
Field(err, 0) = Val_int(errcode);
} else {
err = errconstr;
@@ -264,7 +264,7 @@ void unix_error(int errcode, char *cmdname, value cmdarg)
if (unix_error_exn == NULL)
invalid_argument("Exception Unix.Unix_error not initialized, please link unix.cma");
}
- res = alloc(4, 0);
+ res = alloc_small(4, 0);
Field(res, 0) = *unix_error_exn;
Field(res, 1) = err;
Field(res, 2) = name;
diff --git a/otherlibs/unix/wait.c b/otherlibs/unix/wait.c
index 75151a1f5..3acbbdff7 100644
--- a/otherlibs/unix/wait.c
+++ b/otherlibs/unix/wait.c
@@ -5,7 +5,7 @@
/* Xavier Leroy, projet Cristal, INRIA Rocquencourt */
/* */
/* Copyright 1996 Institut National de Recherche en Informatique et */
-/* Automatique. Distributed only by permission. */
+/* en Automatique. Distributed only by permission. */
/* */
/***********************************************************************/
@@ -39,19 +39,19 @@ static value alloc_process_status(int pid, int status)
value st, res;
if (WIFEXITED(status)) {
- st = alloc(1, TAG_WEXITED);
+ st = alloc_small(1, TAG_WEXITED);
Field(st, 0) = Val_int(WEXITSTATUS(status));
}
else if (WIFSTOPPED(status)) {
- st = alloc(1, TAG_WSTOPPED);
+ st = alloc_small(1, TAG_WSTOPPED);
Field(st, 0) = Val_int(WSTOPSIG(status));
}
else {
- st = alloc(1, TAG_WSIGNALED);
+ st = alloc_small(1, TAG_WSIGNALED);
Field(st, 0) = Val_int(WTERMSIG(status));
}
Begin_root (st);
- res = alloc_tuple(2);
+ res = alloc_small(2, 0);
Field(res, 0) = Val_int(pid);
Field(res, 1) = st;
End_roots();