e43dcf61ea2f4dbf1d2fe2708f10b1a2d42fafe8
[whenjobs.git] / lib / whenutils.ml
1 (* whenjobs
2  * Copyright (C) 2012 Red Hat Inc.
3  *
4  * This program is free software; you can redistribute it and/or modify
5  * it under the terms of the GNU General Public License as published by
6  * the Free Software Foundation; either version 2 of the License, or
7  * (at your option) any later version.
8  *
9  * This program is distributed in the hope that it will be useful,
10  * but WITHOUT ANY WARRANTY; without even the implied warranty of
11  * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
12  * GNU General Public License for more details.
13  *
14  * You should have received a copy of the GNU General Public License along
15  * with this program; if not, write to the Free Software Foundation, Inc.,
16  * 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA.
17  *)
18
19 open Camlp4.PreCast
20 open Ast
21
22 open CalendarLib
23
24 open Big_int
25 open Unix
26 open Printf
27
28 module StringMap = struct
29   include Map.Make (String)
30   let keys m = fold (fun k _ ks -> k :: ks) m []
31   let values m = fold (fun _ v vs -> v :: vs) m []
32 end
33
34 module IntMap = struct
35   include Map.Make (struct type t = int let compare = compare end)
36   let keys m = fold (fun k _ ks -> k :: ks) m []
37   let values m = fold (fun _ v vs -> v :: vs) m []
38 end
39
40 module StringSet = Set.Make (String)
41
42 let (//) = Filename.concat
43
44 let isalpha = function 'a'..'z' | 'A'..'Z' -> true | _ -> false
45 let isalnum = function 'a'..'z' | 'A'..'Z' | '0'..'9' -> true | _ -> false
46
47 let rec filter_map f = function
48   | [] -> []
49   | x :: xs ->
50     match f x with
51     | Some y -> y :: filter_map f xs
52     | None -> filter_map f xs
53
54 type whenexpr =
55   | Expr_unit
56   | Expr_bool of bool
57   | Expr_str of string
58   | Expr_int of Big_int.big_int
59   | Expr_float of float
60   | Expr_var of string
61   | Expr_and of whenexpr * whenexpr
62   | Expr_or of whenexpr * whenexpr
63   | Expr_lt of whenexpr * whenexpr
64   | Expr_le of whenexpr * whenexpr
65   | Expr_eq of whenexpr * whenexpr
66   | Expr_ge of whenexpr * whenexpr
67   | Expr_gt of whenexpr * whenexpr
68   | Expr_not of whenexpr
69   | Expr_add of whenexpr * whenexpr
70   | Expr_sub of whenexpr * whenexpr
71   | Expr_mul of whenexpr * whenexpr
72   | Expr_div of whenexpr * whenexpr
73   | Expr_mod of whenexpr * whenexpr
74   | Expr_changes of string
75   | Expr_increases of string
76   | Expr_decreases of string
77   | Expr_prev of string
78   | Expr_reloaded
79
80 (* This internal type is used during conversion of the OCaml AST
81  * to the whenexpr type.
82  *)
83 type whenexpr_int =
84   | IExpr_unit
85   | IExpr_bool of bool
86   | IExpr_str of string
87   | IExpr_int of Big_int.big_int
88   | IExpr_float of float
89   | IExpr_var of string
90   | IExpr_app of string * whenexpr_int list
91
92 (* Note that days are not necessarily expressible in seconds (because
93  * of leap seconds), months are not expressible in days (because months
94  * have different lengths), and years are not expressible in days
95  * (because of leap days) although we could save a case here by
96  * expressing years in months.
97  *)
98 type periodexpr =
99   | Every_seconds of int
100   | Every_days of int
101   | Every_months of int
102   | Every_years of int
103
104 type shell_script = {
105   sh_loc : Loc.t;
106   sh_script : string;
107 }
108
109 type variable =
110   | T_unit
111   | T_bool of bool
112   | T_string of string
113   | T_int of big_int
114   | T_float of float
115
116 let variable_of_rpc = function
117   | `unit_t -> T_unit
118   | `bool_t b -> T_bool b
119   | `string_t s -> T_string s
120   | `int_t i -> T_int (big_int_of_string i)
121   | `float_t f -> T_float f
122
123 let rpc_of_variable = function
124   | T_unit -> `unit_t
125   | T_bool b -> `bool_t b
126   | T_string s -> `string_t s
127   | T_int i -> `int_t (string_of_big_int i)
128   | T_float f -> `float_t f
129
130 type variables = variable StringMap.t
131
132 type job_private = {
133   (* The result of the previous evaluation.  This is used for
134    * implementing edge-triggering, since we only trigger the job to run
135    * when the state changes from false -> true.
136    *
137    * [None] means there has been no previous evaluation.
138    *)
139   job_prev_eval_state : bool option;
140
141   (* When the job {i ran} last time, we take a copy of the variables.
142    * This allows us to implement the 'changes' operator.
143    *
144    * [None] means there has been no previous run.
145    *)
146   job_prev_variables : variables option;
147 }
148
149 type job_cond =
150   | When_job of whenexpr
151   | Every_job of periodexpr
152
153 type job = {
154   job_loc : Loc.t;
155   job_name : string;
156   job_cond : job_cond;
157   job_script : shell_script;
158   job_private : job_private;
159 }
160
161 let make_when_job _loc name e sh =
162   { job_loc = _loc; job_name = name;
163     job_cond = When_job e; job_script = sh;
164     job_private = { job_prev_eval_state = None;
165                     job_prev_variables = None } }
166
167 let make_every_job _loc name e sh =
168   { job_loc = _loc; job_name = name;
169     job_cond = Every_job e; job_script = sh;
170     job_private = { job_prev_eval_state = None;
171                     job_prev_variables = None } }
172
173 let rec expr_of_ast _loc ast =
174   expr_of_iexpr _loc (iexpr_of_ast _loc ast)
175
176 and iexpr_of_ast _loc = function
177   | ExId (_, IdUid (_, "()")) -> IExpr_unit
178   | ExId (_, IdUid (_, "True")) -> IExpr_bool true
179   | ExId (_, IdUid (_, "False")) -> IExpr_bool false
180   | ExStr (_, str) -> IExpr_str str
181   | ExInt (_, i) -> IExpr_int (big_int_of_string i) (* XXX too large? *)
182   | ExFlo (_, f) -> IExpr_float (float_of_string f)
183   | ExId (_, IdLid (_, id)) -> IExpr_var id
184
185   (* In the OCaml AST, functions are curried right to left, so we
186    * must uncurry to get the list of arguments.
187    *)
188   | ExApp (_, left_tree, right_arg) ->
189     let f, left_args = uncurry_app_tree _loc left_tree in
190     IExpr_app (f, List.rev_map (iexpr_of_ast _loc) (right_arg :: left_args))
191
192   | e ->
193     (* https://groups.google.com/group/fa.caml/browse_thread/thread/f35452d085654bd6 *)
194     eprintf "expr_of_ast: invalid expression: %!";
195     let e = Ast.StExp (_loc, e) in
196     Printers.OCaml.print_implem ~output_file:"/dev/stderr" e;
197
198     invalid_arg (sprintf "%s: invalid expression" (Loc.to_string _loc))
199
200 and uncurry_app_tree _loc = function
201   | ExId (_, IdLid (_, f)) -> f, []
202   | ExApp (_, left_tree, right_arg) ->
203     let f, left_args = uncurry_app_tree _loc left_tree in
204     f, (right_arg :: left_args)
205   | e ->
206     eprintf "uncurry_app_tree: invalid expression: %!";
207     let e = Ast.StExp (_loc, e) in
208     Printers.OCaml.print_implem ~output_file:"/dev/stderr" e;
209
210     invalid_arg (sprintf "%s: invalid expression" (Loc.to_string _loc))
211
212 and expr_of_iexpr _loc = function
213   | IExpr_unit -> Expr_unit
214   | IExpr_bool b -> Expr_bool b
215   | IExpr_str s -> Expr_str s
216   | IExpr_int i -> Expr_int i
217   | IExpr_float f -> Expr_float f
218   | IExpr_var v -> Expr_var v
219
220   | IExpr_app ("&&", exprs) ->
221     two_params _loc "&&" exprs (fun e1 e2 -> Expr_and (e1, e2))
222
223   | IExpr_app ("||", exprs) ->
224     two_params _loc "||" exprs (fun e1 e2 -> Expr_or (e1, e2))
225
226   | IExpr_app ("<", exprs) ->
227     two_params _loc "<" exprs (fun e1 e2 -> Expr_lt (e1, e2))
228
229   | IExpr_app ("<=", exprs) ->
230     two_params _loc "<=" exprs (fun e1 e2 -> Expr_le (e1, e2))
231
232   | IExpr_app (("="|"=="), exprs) ->
233     two_params _loc "=" exprs (fun e1 e2 -> Expr_eq (e1, e2))
234
235   | IExpr_app (">=", exprs) ->
236     two_params _loc ">=" exprs (fun e1 e2 -> Expr_ge (e1, e2))
237
238   | IExpr_app (">", exprs) ->
239     two_params _loc ">" exprs (fun e1 e2 -> Expr_gt (e1, e2))
240
241   | IExpr_app ("!", exprs) ->
242     one_param _loc "!" exprs (fun e1 -> Expr_not e1)
243
244   | IExpr_app ("+", exprs) ->
245     two_params _loc "+" exprs (fun e1 e2 -> Expr_add (e1, e2))
246
247   | IExpr_app ("-", exprs) ->
248     two_params _loc "+" exprs (fun e1 e2 -> Expr_sub (e1, e2))
249
250   | IExpr_app ("*", exprs) ->
251     two_params _loc "+" exprs (fun e1 e2 -> Expr_mul (e1, e2))
252
253   | IExpr_app ("/", exprs) ->
254     two_params _loc "+" exprs (fun e1 e2 -> Expr_div (e1, e2))
255
256   | IExpr_app ("mod", exprs) ->
257     two_params _loc "+" exprs (fun e1 e2 -> Expr_mod (e1, e2))
258
259   | IExpr_app (("change"|"changes"|"changed"), [IExpr_var v]) ->
260     Expr_changes v
261
262   | IExpr_app (("inc"|"increase"|"increases"|"increased"), [IExpr_var v]) ->
263     Expr_increases v
264
265   | IExpr_app (("dec"|"decrease"|"decreases"|"decreased"), [IExpr_var v]) ->
266     Expr_decreases v
267
268   | IExpr_app (("prev"|"previous"), [IExpr_var v]) ->
269     Expr_prev v
270
271   | IExpr_app (("change"|"changes"|"changed"|"inc"|"increase"|"increases"|"increased"|"dec"|"decrease"|"decreases"|"decreased"|"prev"|"previous") as op, _) ->
272     invalid_arg (sprintf "%s: '%s' operator must be followed by a variable name"
273                    (Loc.to_string _loc) op)
274
275   | IExpr_app ("reloaded", [IExpr_unit]) ->
276     Expr_reloaded
277
278   | IExpr_app ("reloaded", _) ->
279     invalid_arg (sprintf "%s: you must use 'reloaded ()'" (Loc.to_string _loc))
280
281   | IExpr_app (op, _) ->
282     invalid_arg (sprintf "%s: unknown operator in expression: %s"
283                    (Loc.to_string _loc) op)
284
285 and two_params _loc op exprs f =
286   match exprs with
287   | [e1; e2] -> f (expr_of_iexpr _loc e1) (expr_of_iexpr _loc e2)
288   | _ ->
289     invalid_arg (sprintf "%s: %s operator must be applied to two parameters"
290                    op (Loc.to_string _loc))
291
292 and one_param _loc op exprs f =
293   match exprs with
294   | [e1] -> f (expr_of_iexpr _loc e1)
295   | _ ->
296     invalid_arg (sprintf "%s: %s operator must be applied to one parameter"
297                    op (Loc.to_string _loc))
298
299 let rec string_of_whenexpr = function
300   | Expr_unit -> "()"
301   | Expr_bool b -> sprintf "%b" b
302   | Expr_str s -> sprintf "%S" s
303   | Expr_int i -> sprintf "%s" (string_of_big_int i)
304   | Expr_float f -> sprintf "%f" f
305   | Expr_var v -> sprintf "%s" v
306   | Expr_and (e1, e2) ->
307     sprintf "%s && %s" (string_of_whenexpr e1) (string_of_whenexpr e2)
308   | Expr_or (e1, e2) ->
309     sprintf "%s || %s" (string_of_whenexpr e1) (string_of_whenexpr e2)
310   | Expr_lt (e1, e2) ->
311     sprintf "%s < %s" (string_of_whenexpr e1) (string_of_whenexpr e2)
312   | Expr_le (e1, e2) ->
313     sprintf "%s <= %s" (string_of_whenexpr e1) (string_of_whenexpr e2)
314   | Expr_eq (e1, e2) ->
315     sprintf "%s == %s" (string_of_whenexpr e1) (string_of_whenexpr e2)
316   | Expr_ge (e1, e2) ->
317     sprintf "%s >= %s" (string_of_whenexpr e1) (string_of_whenexpr e2)
318   | Expr_gt (e1, e2) ->
319     sprintf "%s > %s" (string_of_whenexpr e1) (string_of_whenexpr e2)
320   | Expr_not e -> sprintf "! %s" (string_of_whenexpr e)
321   | Expr_add (e1, e2) ->
322     sprintf "%s + %s" (string_of_whenexpr e1) (string_of_whenexpr e2)
323   | Expr_sub (e1, e2) ->
324     sprintf "%s - %s" (string_of_whenexpr e1) (string_of_whenexpr e2)
325   | Expr_mul (e1, e2) ->
326     sprintf "%s * %s" (string_of_whenexpr e1) (string_of_whenexpr e2)
327   | Expr_div (e1, e2) ->
328     sprintf "%s / %s" (string_of_whenexpr e1) (string_of_whenexpr e2)
329   | Expr_mod (e1, e2) ->
330     sprintf "%s mod %s" (string_of_whenexpr e1) (string_of_whenexpr e2)
331   | Expr_changes v -> sprintf "changes %s" v
332   | Expr_increases v -> sprintf "increases %s" v
333   | Expr_decreases v -> sprintf "decreases %s" v
334   | Expr_prev v -> sprintf "prev %s" v
335   | Expr_reloaded -> "reloaded ()"
336
337 let string_of_periodexpr = function
338   | Every_seconds 1 -> "1 second"
339   | Every_seconds i -> sprintf "%d seconds" i
340   | Every_days 1 -> "1 day"
341   | Every_days i -> sprintf "%d days" i
342   | Every_months 1 -> "1 month"
343   | Every_months i -> sprintf "%d months" i
344   | Every_years 1 -> "1 year"
345   | Every_years i -> sprintf "%d years" i
346
347 let rec dependencies_of_whenexpr = function
348   | Expr_unit -> []
349   | Expr_bool _ -> []
350   | Expr_str _ -> []
351   | Expr_int _ -> []
352   | Expr_float _ -> []
353   | Expr_var v -> [v]
354   | Expr_and (e1, e2)
355   | Expr_or (e1, e2)
356   | Expr_lt (e1, e2)
357   | Expr_le (e1, e2)
358   | Expr_eq (e1, e2)
359   | Expr_ge (e1, e2)
360   | Expr_gt (e1, e2)
361   | Expr_add (e1, e2)
362   | Expr_sub (e1, e2)
363   | Expr_mul (e1, e2)
364   | Expr_div (e1, e2)
365   | Expr_mod (e1, e2) ->
366     dependencies_of_whenexpr e1 @ dependencies_of_whenexpr e2
367   | Expr_not e ->
368     dependencies_of_whenexpr e
369   | Expr_changes v
370   | Expr_increases v
371   | Expr_decreases v
372   | Expr_prev v -> [v]
373   | Expr_reloaded -> []
374
375 let dependencies_of_job = function
376   | { job_cond = When_job whenexpr } -> dependencies_of_whenexpr whenexpr
377   | { job_cond = Every_job _ } -> []
378
379 let rec eval_whenexpr job variables onload = function
380   | Expr_unit -> T_unit
381   | Expr_bool b -> T_bool b
382   | Expr_str s -> T_string s
383   | Expr_int i -> T_int i
384   | Expr_float f -> T_float f
385
386   | Expr_var v ->
387     get_variable variables v
388
389   | Expr_and (e1, e2) ->
390     if eval_whenexpr_as_bool job variables onload e1 &&
391        eval_whenexpr_as_bool job variables onload e2 then
392       T_bool true
393     else
394       T_bool false
395
396   | Expr_or (e1, e2) ->
397     if eval_whenexpr_as_bool job variables onload e1 ||
398        eval_whenexpr_as_bool job variables onload e2 then
399       T_bool true
400     else
401       T_bool false
402
403   | Expr_lt (e1, e2) ->
404     let e1 = eval_whenexpr job variables onload e1
405     and e2 = eval_whenexpr job variables onload e2 in
406     if compare_values e1 e2 < 0 then
407       T_bool true
408     else
409       T_bool false
410
411   | Expr_le (e1, e2) ->
412     let e1 = eval_whenexpr job variables onload e1
413     and e2 = eval_whenexpr job variables onload e2 in
414     if compare_values e1 e2 <= 0 then
415       T_bool true
416     else
417       T_bool false
418
419   | Expr_eq (e1, e2) ->
420     let e1 = eval_whenexpr job variables onload e1
421     and e2 = eval_whenexpr job variables onload e2 in
422     if compare_values e1 e2 = 0 then
423       T_bool true
424     else
425       T_bool false
426
427   | Expr_ge (e1, e2) ->
428     let e1 = eval_whenexpr job variables onload e1
429     and e2 = eval_whenexpr job variables onload e2 in
430     if compare_values e1 e2 >= 0 then
431       T_bool true
432     else
433       T_bool false
434
435   | Expr_gt (e1, e2) ->
436     let e1 = eval_whenexpr job variables onload e1
437     and e2 = eval_whenexpr job variables onload e2 in
438     if compare_values e1 e2 > 0 then
439       T_bool true
440     else
441       T_bool false
442
443   | Expr_not e ->
444     if not (eval_whenexpr_as_bool job variables onload e) then
445       T_bool true
446     else
447       T_bool false
448
449   | Expr_add (e1, e2) ->
450     let e1 = eval_whenexpr job variables onload e1
451     and e2 = eval_whenexpr job variables onload e2 in
452     add_values e1 e2
453
454   | Expr_sub (e1, e2) ->
455     let e1 = eval_whenexpr job variables onload e1
456     and e2 = eval_whenexpr job variables onload e2 in
457     sub_values e1 e2
458
459   | Expr_mul (e1, e2) ->
460     let e1 = eval_whenexpr job variables onload e1
461     and e2 = eval_whenexpr job variables onload e2 in
462     mul_values e1 e2
463
464   | Expr_div (e1, e2) ->
465     let e1 = eval_whenexpr job variables onload e1
466     and e2 = eval_whenexpr job variables onload e2 in
467     div_values e1 e2
468
469   | Expr_mod (e1, e2) ->
470     let e1 = eval_whenexpr job variables onload e1
471     and e2 = eval_whenexpr job variables onload e2 in
472     mod_values e1 e2
473
474   | Expr_changes v ->
475     let prev_value, curr_value = get_prev_curr_value job variables v in
476     if compare_values prev_value curr_value <> 0 then
477       T_bool true
478     else
479       T_bool false
480
481   | Expr_increases v ->
482     let prev_value, curr_value = get_prev_curr_value job variables v in
483     if compare_values prev_value curr_value > 0 then
484       T_bool true
485     else
486       T_bool false
487
488   | Expr_decreases v ->
489     let prev_value, curr_value = get_prev_curr_value job variables v in
490     if compare_values prev_value curr_value < 0 then
491       T_bool true
492     else
493       T_bool false
494
495   | Expr_prev v ->
496     get_prev_variable job v
497
498   | Expr_reloaded ->
499     T_bool onload
500
501 and get_prev_curr_value job variables v =
502   let prev_value = get_prev_variable job v in
503   let curr_value = get_variable variables v in
504   prev_value, curr_value
505
506 and get_variable variables v =
507   try StringMap.find v variables with Not_found -> T_string ""
508
509 and get_prev_variable job v =
510   match job.job_private.job_prev_variables with
511   | None ->
512     (* Job has never run.  XXX Should do better here. *)
513     T_string ""
514   | Some prev_variables ->
515     get_variable prev_variables v
516
517 (* Call {!eval_whenexpr} and cast the result to a boolean. *)
518 and eval_whenexpr_as_bool job variables onload expr =
519   match eval_whenexpr job variables onload expr with
520   | T_unit -> false
521   | T_bool r -> r
522   | T_string s -> s <> ""
523   | T_int i -> sign_big_int i <> 0
524   | T_float f -> f <> 0.
525
526 (* Do a comparison on two typed values and return -1/0/+1.  If the
527  * types are different then we compare the values as strings.  The user
528  * can avoid this by specifying types.
529  *)
530 and compare_values value1 value2 =
531   match value1, value2 with
532   | T_bool b1, T_bool b2 -> compare b1 b2
533   | T_string s1, T_string s2 -> compare s1 s2
534   | T_int i1, T_int i2 -> compare_big_int i1 i2
535   | T_float f1, T_float f2 -> compare f1 f2
536   | _ ->
537     let value1 = string_of_variable value1
538     and value2 = string_of_variable value2 in
539     compare value1 value2
540
541 (* + operator is addition or string concatenation. *)
542 and add_values value1 value2 =
543   match value1, value2 with
544   | T_int i1, T_int i2 -> T_int (add_big_int i1 i2)
545   | T_float i1, T_float i2 -> T_float (i1 +. i2)
546   | T_int i1, T_float i2 -> T_float (float_of_big_int i1 +. i2)
547   | T_float i1, T_int i2 -> T_float (i1 +. float_of_big_int i2)
548   | T_string i1, T_string i2 -> T_string (i1 ^ i2)
549   | _ ->
550     invalid_arg
551       (sprintf "incompatible types in addition: %s + %s"
552          (printable_string_of_variable value1)
553          (printable_string_of_variable value2))
554
555 and sub_values value1 value2 =
556   match value1, value2 with
557   | T_int i1, T_int i2 -> T_int (sub_big_int i1 i2)
558   | T_float i1, T_float i2 -> T_float (i1 -. i2)
559   | T_int i1, T_float i2 -> T_float (float_of_big_int i1 -. i2)
560   | T_float i1, T_int i2 -> T_float (i1 -. float_of_big_int i2)
561   | _ ->
562     invalid_arg
563       (sprintf "incompatible types in subtraction: %s - %s"
564          (printable_string_of_variable value1)
565          (printable_string_of_variable value2))
566
567 and mul_values value1 value2 =
568   match value1, value2 with
569   | T_int i1, T_int i2 -> T_int (mult_big_int i1 i2)
570   | T_float i1, T_float i2 -> T_float (i1 *. i2)
571   | T_int i1, T_float i2 -> T_float (float_of_big_int i1 *. i2)
572   | T_float i1, T_int i2 -> T_float (i1 *. float_of_big_int i2)
573   | _ ->
574     invalid_arg
575       (sprintf "incompatible types in multiplication: %s * %s"
576          (printable_string_of_variable value1)
577          (printable_string_of_variable value2))
578
579 and div_values value1 value2 =
580   match value1, value2 with
581   | T_int i1, T_int i2 -> T_int (div_big_int i1 i2)
582   | T_float i1, T_float i2 -> T_float (i1 /. i2)
583   | T_int i1, T_float i2 -> T_float (float_of_big_int i1 /. i2)
584   | T_float i1, T_int i2 -> T_float (i1 /. float_of_big_int i2)
585   | _ ->
586     invalid_arg
587       (sprintf "incompatible types in division: %s / %s"
588          (printable_string_of_variable value1)
589          (printable_string_of_variable value2))
590
591 and mod_values value1 value2 =
592   match value1, value2 with
593   | T_int i1, T_int i2 -> T_int (mod_big_int i1 i2)
594   | T_float i1, T_float i2 -> T_float (mod_float i1 i2)
595   | T_int i1, T_float i2 -> T_float (mod_float (float_of_big_int i1) i2)
596   | T_float i1, T_int i2 -> T_float (mod_float i1 (float_of_big_int i2))
597   | _ ->
598     invalid_arg
599       (sprintf "incompatible types in modulo: %s mod %s"
600          (printable_string_of_variable value1)
601          (printable_string_of_variable value2))
602
603 and string_of_variable = function
604   | T_unit -> "" (* for string_of_variable, we don't want () here *)
605   | T_bool b -> string_of_bool b
606   | T_string s -> s
607   | T_int i -> string_of_big_int i
608   | T_float f -> string_of_float f
609
610 and printable_string_of_variable = function
611   | T_unit -> "()"
612   | T_bool b -> string_of_bool b
613   | T_string s -> sprintf "%S" s
614   | T_int i -> string_of_big_int i
615   | T_float f -> string_of_float f
616
617 let job_evaluate job variables onload =
618   match job with
619   | { job_cond = Every_job _ } -> false, job
620   | { job_cond = When_job whenexpr } ->
621     let state = eval_whenexpr_as_bool job variables onload whenexpr in
622
623     (* Because jobs are edge-triggered, we're only interested in the
624      * case where the evaluation state changes from false -> true.
625      *)
626     match job.job_private.job_prev_eval_state, state with
627     | None, false
628     | Some false, false
629     | Some true, true
630     | Some true, false ->
631       let jobp = { job.job_private with job_prev_eval_state = Some state } in
632       let job = { job with job_private = jobp } in
633       false, job
634
635     | None, true
636     | Some false, true ->
637       let jobp = { job_prev_eval_state = Some true;
638                    job_prev_variables = Some variables } in
639       let job = { job with job_private = jobp } in
640       true, job
641
642 let next_periodexpr =
643   (* Round up 'a' to the next multiple of 'i'. *)
644   let round_up_float a i =
645     let r = mod_float a i in
646     if r = 0. then a +. i else a +. (i -. r)
647   and round_up a i =
648     let r = a mod i in
649     if r = 0 then a + i else a + (i - r)
650   in
651
652   fun t -> function
653   | Every_seconds i ->
654     let i = float_of_int i in
655     round_up_float t i
656
657   | Every_years i ->
658     let tm = gmtime t in
659
660     (* Round 'tm' up to the first day of the next year. *)
661     let year = round_up tm.tm_year i in
662     let tm = { tm with tm_sec = 0; tm_min = 0; tm_hour = 0;
663                        tm_mday = 1; tm_mon = 0; tm_year = year } in
664     fst (mktime tm)
665
666   | Every_days i ->
667     let t = Date.from_unixfloat t in
668     let t0 = Date.make 1970 1 1 in
669
670     (* Number of whole days since Unix Epoch. *)
671     let nb_days = Date.Period.safe_nb_days (Date.sub t t0) in
672
673     let nb_days = round_up nb_days i in
674     let t' = Date.add t0 (Date.Period.day nb_days) in
675     Date.to_unixfloat t'
676
677   | Every_months i ->
678     (* Calculate number of whole months since Unix Epoch. *)
679     let tm = gmtime t in
680     let months = 12 * (tm.tm_year - 70) + tm.tm_mon in
681
682     let months = round_up months i in
683     let t0 = Date.make 1970 1 1 in
684     let t' = Date.add t0 (Date.Period.month months) in
685     Date.to_unixfloat t'