Adaptation au nouvesu format de records flottants.
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@1975 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02master
parent
4cdadc0c6d
commit
6632b8bdb2
|
@ -27,21 +27,6 @@
|
|||
tv.tv_usec = (int) (1e6 * ((d) - tv.tv_sec))
|
||||
|
||||
static value unix_convert_itimer(struct itimerval *tp)
|
||||
{
|
||||
value res;
|
||||
value interval = Val_unit, v = Val_unit;
|
||||
|
||||
Begin_roots2(interval, v);
|
||||
interval = copy_double(Get_timeval(tp->it_interval));
|
||||
v = copy_double(Get_timeval(tp->it_value));
|
||||
res = alloc_tuple(2);
|
||||
Field(res, 0) = interval;
|
||||
Field(res, 1) = v;
|
||||
End_roots();
|
||||
return res;
|
||||
}
|
||||
|
||||
static value unix_convert_itimer_native(struct itimerval *tp)
|
||||
{
|
||||
value res = alloc(Double_wosize * 2, Double_array_tag);
|
||||
Store_double_field(res, 0, Get_timeval(tp->it_interval));
|
||||
|
@ -52,23 +37,13 @@ static value unix_convert_itimer_native(struct itimerval *tp)
|
|||
static int itimers[3] = { ITIMER_REAL, ITIMER_VIRTUAL, ITIMER_PROF };
|
||||
|
||||
value unix_setitimer(value which, value newval)
|
||||
{
|
||||
struct itimerval new, old;
|
||||
Set_timeval(new.it_interval, Double_val(Field(newval, 0)));
|
||||
Set_timeval(new.it_value, Double_val(Field(newval, 1)));
|
||||
if (setitimer(itimers[Int_val(which)], &new, &old) == -1)
|
||||
uerror("setitimer", Nothing);
|
||||
return unix_convert_itimer(&old);
|
||||
}
|
||||
|
||||
value unix_setitimer_native(value which, value newval)
|
||||
{
|
||||
struct itimerval new, old;
|
||||
Set_timeval(new.it_interval, Double_field(newval, 0));
|
||||
Set_timeval(new.it_value, Double_field(newval, 1));
|
||||
if (setitimer(itimers[Int_val(which)], &new, &old) == -1)
|
||||
uerror("setitimer", Nothing);
|
||||
return unix_convert_itimer_native(&old);
|
||||
return unix_convert_itimer(&old);
|
||||
}
|
||||
|
||||
value unix_getitimer(value which)
|
||||
|
@ -79,23 +54,11 @@ value unix_getitimer(value which)
|
|||
return unix_convert_itimer(&val);
|
||||
}
|
||||
|
||||
value unix_getitimer_native(value which)
|
||||
{
|
||||
struct itimerval val;
|
||||
if (getitimer(itimers[Int_val(which)], &val) == -1)
|
||||
uerror("getitimer", Nothing);
|
||||
return unix_convert_itimer_native(&val);
|
||||
}
|
||||
|
||||
#else
|
||||
|
||||
value unix_setitimer(value which, value newval)
|
||||
{ invalid_argument("setitimer not implemented"); }
|
||||
value unix_getitimer(value which)
|
||||
{ invalid_argument("getitimer not implemented"); }
|
||||
value unix_setitimer_native(value which, value newval)
|
||||
{ invalid_argument("setitimer not implemented"); }
|
||||
value unix_getitimer_native(value which)
|
||||
{ invalid_argument("getitimer not implemented"); }
|
||||
|
||||
#endif
|
||||
|
|
|
@ -27,28 +27,7 @@
|
|||
#endif
|
||||
#endif
|
||||
|
||||
value unix_times_bytecode(void) /* ML */
|
||||
{
|
||||
value res;
|
||||
struct tms buffer;
|
||||
value u = Val_unit, s = Val_unit, cu = Val_unit, cs = Val_unit;
|
||||
|
||||
Begin_roots4 (u, s, cu, cs);
|
||||
times(&buffer);
|
||||
u = copy_double((double) buffer.tms_utime / CLK_TCK);
|
||||
s = copy_double((double) buffer.tms_stime / CLK_TCK);
|
||||
cu = copy_double((double) buffer.tms_cutime / CLK_TCK);
|
||||
cs = copy_double((double) buffer.tms_cstime / CLK_TCK);
|
||||
res = alloc_tuple(4);
|
||||
Field (res, 0) = u;
|
||||
Field (res, 1) = s;
|
||||
Field (res, 2) = cu;
|
||||
Field (res, 3) = cs;
|
||||
End_roots();
|
||||
return res;
|
||||
}
|
||||
|
||||
value unix_times_native(void) /* ML */
|
||||
value unix_times(void) /* ML */
|
||||
{
|
||||
value res;
|
||||
struct tms buffer;
|
||||
|
|
|
@ -289,8 +289,7 @@ external localtime : int -> tm = "unix_localtime"
|
|||
external mktime : tm -> int * tm = "unix_mktime"
|
||||
external alarm : int -> int = "unix_alarm"
|
||||
external sleep : int -> unit = "unix_sleep"
|
||||
external times : unit -> process_times =
|
||||
"unix_times_bytecode" "unix_times_native"
|
||||
external times : unit -> process_times = "unix_times"
|
||||
external utimes : string -> int -> int -> unit = "unix_utimes"
|
||||
|
||||
type interval_timer =
|
||||
|
@ -302,11 +301,10 @@ type interval_timer_status =
|
|||
{ it_interval: float; (* Period *)
|
||||
it_value: float } (* Current value of the timer *)
|
||||
|
||||
external getitimer: interval_timer -> interval_timer_status
|
||||
= "unix_getitimer" "unix_getitimer_native"
|
||||
external getitimer: interval_timer -> interval_timer_status = "unix_getitimer"
|
||||
external setitimer:
|
||||
interval_timer -> interval_timer_status -> interval_timer_status
|
||||
= "unix_setitimer" "unix_setitimer_native"
|
||||
= "unix_setitimer"
|
||||
|
||||
external getuid : unit -> int = "unix_getuid"
|
||||
external geteuid : unit -> int = "unix_geteuid"
|
||||
|
|
Loading…
Reference in New Issue