summaryrefslogtreecommitdiffstats
path: root/otherlibs/unix
diff options
context:
space:
mode:
Diffstat (limited to 'otherlibs/unix')
-rw-r--r--otherlibs/unix/.depend2
-rw-r--r--otherlibs/unix/Makefile5
-rw-r--r--otherlibs/unix/pause.c21
-rw-r--r--otherlibs/unix/signals.c74
-rw-r--r--otherlibs/unix/unix.ml9
-rw-r--r--otherlibs/unix/unix.mli24
6 files changed, 108 insertions, 27 deletions
diff --git a/otherlibs/unix/.depend b/otherlibs/unix/.depend
index 707cfafb3..f73969a88 100644
--- a/otherlibs/unix/.depend
+++ b/otherlibs/unix/.depend
@@ -55,7 +55,6 @@ mkfifo.o: mkfifo.c unixsupport.h
nice.o: nice.c unixsupport.h
open.o: open.c unixsupport.h
opendir.o: opendir.c unixsupport.h
-pause.o: pause.c unixsupport.h
pipe.o: pipe.c unixsupport.h
putenv.o: putenv.c unixsupport.h
read.o: read.c unixsupport.h
@@ -70,6 +69,7 @@ setgid.o: setgid.c unixsupport.h
setsid.o: setsid.c unixsupport.h
setuid.o: setuid.c unixsupport.h
shutdown.o: shutdown.c unixsupport.h
+signals.o: signals.c unixsupport.h
sleep.o: sleep.c unixsupport.h
socket.o: socket.c unixsupport.h
socketaddr.o: socketaddr.c unixsupport.h socketaddr.h
diff --git a/otherlibs/unix/Makefile b/otherlibs/unix/Makefile
index 9caa71e94..ed085512d 100644
--- a/otherlibs/unix/Makefile
+++ b/otherlibs/unix/Makefile
@@ -16,9 +16,10 @@ OBJS=accept.o access.o addrofstr.o alarm.o bind.o chdir.o chmod.o \
getlogin.o getpeername.o getpid.o getppid.o getproto.o getpw.o \
gettimeofday.o getserv.o getsockname.o getuid.o \
gmtime.o itimer.o kill.o link.o listen.o lockf.o lseek.o mkdir.o \
- mkfifo.o nice.o open.o opendir.o pause.o pipe.o putenv.o read.o \
+ mkfifo.o nice.o open.o opendir.o pipe.o putenv.o read.o \
readdir.o readlink.o rename.o rewinddir.o rmdir.o select.o sendrecv.o \
- setgid.o setsid.o setuid.o shutdown.o sleep.o socket.o socketaddr.o \
+ setgid.o setsid.o setuid.o shutdown.o signals.o \
+ sleep.o socket.o socketaddr.o \
socketpair.o sockopt.o stat.o strofaddr.o symlink.o termios.o \
time.o times.o truncate.o umask.o unixsupport.o unlink.o \
utimes.o wait.o write.o
diff --git a/otherlibs/unix/pause.c b/otherlibs/unix/pause.c
deleted file mode 100644
index 275853038..000000000
--- a/otherlibs/unix/pause.c
+++ /dev/null
@@ -1,21 +0,0 @@
-/***********************************************************************/
-/* */
-/* Objective Caml */
-/* */
-/* Xavier Leroy, projet Cristal, INRIA Rocquencourt */
-/* */
-/* Copyright 1996 Institut National de Recherche en Informatique et */
-/* Automatique. Distributed only by permission. */
-/* */
-/***********************************************************************/
-
-/* $Id$ */
-
-#include <mlvalues.h>
-#include "unixsupport.h"
-
-value unix_pause(void) /* ML */
-{
- pause();
- return Val_unit;
-}
diff --git a/otherlibs/unix/signals.c b/otherlibs/unix/signals.c
new file mode 100644
index 000000000..4d17b10a7
--- /dev/null
+++ b/otherlibs/unix/signals.c
@@ -0,0 +1,74 @@
+/***********************************************************************/
+/* */
+/* Objective Caml */
+/* */
+/* Xavier Leroy, projet Cristal, INRIA Rocquencourt */
+/* */
+/* Copyright 1998 Institut National de Recherche en Informatique et */
+/* Automatique. Distributed only by permission. */
+/* */
+/***********************************************************************/
+
+/* $Id$ */
+
+#include <errno.h>
+#include <signal.h>
+
+#include <alloc.h>
+#include <memory.h>
+#include <mlvalues.h>
+#include "unixsupport.h"
+
+static void decode_sigset(value vset, sigset_t * set)
+{
+ sigemptyset(set);
+ while (vset != Val_int(0)) {
+ sigaddset(set, Int_val(Field(vset, 0)));
+ vset = Field(vset, 1);
+ }
+}
+
+static value encode_sigset(sigset_t * set)
+{
+ value res = Val_int(0);
+ int i;
+
+ Begin_root(res)
+ for (i = 1; i < NSIG; i++)
+ if (sigismember(set, i)) {
+ value newcons = alloc(2, 0);
+ Field(newcons, 0) = Val_int(i);
+ Field(newcons, 1) = res;
+ res = newcons;
+ }
+ End_roots();
+ return res;
+}
+
+static int sigprocmask_cmd[3] = { SIG_SETMASK, SIG_BLOCK, SIG_UNBLOCK };
+
+value unix_sigprocmask(value vaction, value vset) /* ML */
+{
+ int how;
+ sigset_t set, oldset;
+
+ how = sigprocmask_cmd[Int_val(vaction)];
+ decode_sigset(vset, &set);
+ if (sigprocmask(how, &set, &oldset) == -1) uerror("sigprocmask", Nothing);
+ return encode_sigset(&oldset);
+}
+
+value unix_sigpending(value unit) /* ML */
+{
+ sigset_t pending;
+ if (sigpending(&pending) == -1) uerror("sigpending", Nothing);
+ return encode_sigset(&pending);
+}
+
+value unix_sigsuspend(value vset) /* ML */
+{
+ sigset_t set;
+ decode_sigset(vset, &set);
+ if (sigsuspend(&set) == -1 && errno != EINTR) uerror("sigsuspend", Nothing);
+ return Val_unit;
+}
diff --git a/otherlibs/unix/unix.ml b/otherlibs/unix/unix.ml
index 216a75c72..78b6d9597 100644
--- a/otherlibs/unix/unix.ml
+++ b/otherlibs/unix/unix.ml
@@ -259,7 +259,14 @@ type lock_command =
external lockf : file_descr -> lock_command -> int -> unit = "unix_lockf"
external kill : int -> int -> unit = "unix_kill"
-external pause : unit -> unit = "unix_pause"
+type sigprocmask_command = SIG_SETMASK | SIG_BLOCK | SIG_UNBLOCK
+external sigprocmask: sigprocmask_command -> int list -> int list
+ = "unix_sigprocmask"
+external sigpending: unit -> int list = "unix_sigpending"
+external sigsuspend: int list -> unit = "unix_sigsuspend"
+
+let pause() =
+ let sigs = sigprocmask SIG_BLOCK [] in sigsuspend sigs
type process_times =
{ tms_utime : float;
diff --git a/otherlibs/unix/unix.mli b/otherlibs/unix/unix.mli
index 55167c2d3..0f55c1a34 100644
--- a/otherlibs/unix/unix.mli
+++ b/otherlibs/unix/unix.mli
@@ -492,9 +492,29 @@ val lockf : file_descr -> lock_command -> int -> unit
val kill : int -> int -> unit
(* [kill pid sig] sends signal number [sig] to the process
with id [pid]. *)
-val pause : unit -> unit
- (* Wait until a non-ignored signal is delivered. *)
+type sigprocmask_command = SIG_SETMASK | SIG_BLOCK | SIG_UNBLOCK
+
+val sigprocmask: sigprocmask_command -> int list -> int list
+ (* [sigprocmask cmd sigs] changes the set of blocked signals.
+ If [cmd] is [SIG_SETMASK], blocked signals are set to those in
+ the list [sigs].
+ If [cmd] is [SIG_BLOCK], the signals in [sigs] are added to
+ the set of blocked signals.
+ If [cmd] is [SIG_UNBLOCK], the signals in [sigs] are removed
+ from the set of blocked signals.
+ [sigprocmask] returns the set of previously blocked signals. *)
+
+val sigpending: unit -> int list
+ (* Return the set of blocked signals that are currently pending. *)
+
+val sigsuspend: int list -> unit
+ (* [sigsuspend sigs] atomically sets the blocked signals to [sig]
+ and waits for a non-ignored, non-blocked signal to be delivered.
+ On return, the blocked signals are reset to their initial value. *)
+
+val pause : unit -> unit
+ (* Wait until a non-ignored, non-blocked signal is delivered. *)
(*** Time functions *)