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