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