summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorXavier Leroy <xavier.leroy@inria.fr>1998-04-30 13:30:03 +0000
committerXavier Leroy <xavier.leroy@inria.fr>1998-04-30 13:30:03 +0000
commit11a4c45b78e72c4038a24023eea5c243c0624ca9 (patch)
tree0c82b52068db17ac73d5aedb9e62abe31b9ef3e0
parenta17c38778c24e609f6c743e261d0b5dfbcc5e42b (diff)
Ajout de putenv et getenv.
Dams mktime: ignorer le champ is_dst fourni en argument. git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@1947 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r--otherlibs/unix/.depend1
-rw-r--r--otherlibs/unix/Makefile2
-rw-r--r--otherlibs/unix/gmtime.c2
-rw-r--r--otherlibs/unix/putenv.c43
-rw-r--r--otherlibs/unix/unix.ml2
-rw-r--r--otherlibs/unix/unix.mli20
6 files changed, 63 insertions, 7 deletions
diff --git a/otherlibs/unix/.depend b/otherlibs/unix/.depend
index 8bc3e3894..707cfafb3 100644
--- a/otherlibs/unix/.depend
+++ b/otherlibs/unix/.depend
@@ -57,6 +57,7 @@ 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
readdir.o: readdir.c unixsupport.h
readlink.o: readlink.c unixsupport.h
diff --git a/otherlibs/unix/Makefile b/otherlibs/unix/Makefile
index c7dbb8af4..9caa71e94 100644
--- a/otherlibs/unix/Makefile
+++ b/otherlibs/unix/Makefile
@@ -16,7 +16,7 @@ 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 read.o \
+ mkfifo.o nice.o open.o opendir.o pause.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 \
socketpair.o sockopt.o stat.o strofaddr.o symlink.o termios.o \
diff --git a/otherlibs/unix/gmtime.c b/otherlibs/unix/gmtime.c
index 3ade3ec95..c1c0459db 100644
--- a/otherlibs/unix/gmtime.c
+++ b/otherlibs/unix/gmtime.c
@@ -65,7 +65,7 @@ value unix_mktime(value t) /* ML */
tm.tm_year = Int_val(Field(t, 5));
tm.tm_wday = Int_val(Field(t, 6));
tm.tm_yday = Int_val(Field(t, 7));
- tm.tm_isdst = Bool_val(Field(t, 8));
+ tm.tm_isdst = -1; /* tm.tm_isdst = Bool_val(Field(t, 8)); */
clock = mktime(&tm);
tmval = alloc_tm(&tm);
res = alloc_tuple(2);
diff --git a/otherlibs/unix/putenv.c b/otherlibs/unix/putenv.c
new file mode 100644
index 000000000..0e5accc4b
--- /dev/null
+++ b/otherlibs/unix/putenv.c
@@ -0,0 +1,43 @@
+/***********************************************************************/
+/* */
+/* Objective Caml */
+/* */
+/* Xavier Leroy, projet Cristal, INRIA Rocquencourt */
+/* */
+/* Copyright 1998 Institut National de Recherche en Informatique et */
+/* Automatique. Distributed only by permission. */
+/* */
+/***********************************************************************/
+
+/* $Id$ */
+
+#include <memory.h>
+#include <mlvalues.h>
+#include <str.h>
+#include "unixsupport.h"
+
+#ifdef HAS_PUTENV
+
+#include <stdlib.h>
+#include <string.h>
+
+value unix_putenv(value name, value val) /* ML */
+{
+ mlsize_t namelen = string_length(name);
+ mlsize_t vallen = string_length(val);
+ char * s = (char *) stat_alloc(namelen + 1 + vallen + 1);
+
+ bcopy(String_val(name), s, namelen);
+ s[namelen] = '=';
+ bcopy(String_val(val), s + namelen + 1, vallen);
+ s[namelen + 1 + vallen] = 0;
+ if (putenv(s) == -1) uerror("putenv", name);
+ return Val_unit;
+}
+
+#else
+
+value unix_putenv(value name, value val) /* ML */
+{ invalid_argument("putenv not implemented"); }
+
+#endif
diff --git a/otherlibs/unix/unix.ml b/otherlibs/unix/unix.ml
index 1f2b35c19..d368d37d7 100644
--- a/otherlibs/unix/unix.ml
+++ b/otherlibs/unix/unix.ml
@@ -106,6 +106,8 @@ let handle_unix_error f arg =
exit 2
external environment : unit -> string array = "unix_environment"
+external getenv: string -> string = "sys_getenv"
+external putenv: string -> string -> unit = "unix_putenv"
type process_status =
WEXITED of int
diff --git a/otherlibs/unix/unix.mli b/otherlibs/unix/unix.mli
index 100d85c6b..5e59c8163 100644
--- a/otherlibs/unix/unix.mli
+++ b/otherlibs/unix/unix.mli
@@ -105,11 +105,20 @@ val handle_unix_error : ('a -> 'b) -> 'a -> 'b
describing the error and exits with code 2. *)
-(*** Interface with the parent process *)
+(*** Access to the process environment *)
external environment : unit -> string array = "unix_environment"
(* Return the process environment, as an array of strings
- with the format ``variable=value''. See also [Sys.getenv]. *)
+ with the format ``variable=value''. *)
+external getenv: string -> string = "sys_getenv"
+ (* Return the value associated to a variable in the process
+ environment. Raise [Not_found] if the variable is unbound.
+ (This function is identical to [Sys.getenv].) *)
+external putenv: string -> string -> unit = "unix_putenv"
+ (* [Unix.putenv name value] sets the value associated to a
+ variable in the process environment.
+ [name] is the name of the environment variable,
+ and [value] its new associated value. *)
(*** Process handling *)
@@ -519,15 +528,16 @@ external gettimeofday : unit -> float = "unix_gettimeofday"
(* Same as [time], but with resolution better than 1 second. *)
external gmtime : int -> tm = "unix_gmtime"
(* Convert a time in seconds, as returned by [time], into a date and
- a time. Assumes Greenwich meridian time zone. *)
+ a time. Assumes Greenwich meridian time zone, also known as UTC. *)
external localtime : int -> tm = "unix_localtime"
(* Convert a time in seconds, as returned by [time], into a date and
a time. Assumes the local time zone. *)
external mktime : tm -> int * tm = "unix_mktime"
(* Convert a date and time, specified by the [tm] argument, into
a time in seconds, as returned by [time]. Also return a normalized
- copy of the given [tm] record, with the [tm_wday] and [tm_yday]
- recomputed from the other fields. *)
+ copy of the given [tm] record, with the [tm_wday], [tm_yday],
+ and [tm_isdst] fields recomputed from the other fields.
+ The [tm] argument is interpreted in the local time zone. *)
external alarm : int -> int = "unix_alarm"
(* Schedule a [SIGALRM] signals after the given number of seconds. *)
external sleep : int -> unit = "unix_sleep"