d53ac7e852e0cdbe02bfcf2c353b81486de3a23d
[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_bool of bool
56   | Expr_str of string
57   | Expr_int of Big_int.big_int
58   | Expr_float of float
59   | Expr_var of string
60   | Expr_and of whenexpr * whenexpr
61   | Expr_or of whenexpr * whenexpr
62   | Expr_lt of whenexpr * whenexpr
63   | Expr_le of whenexpr * whenexpr
64   | Expr_eq of whenexpr * whenexpr
65   | Expr_ge of whenexpr * whenexpr
66   | Expr_gt of whenexpr * whenexpr
67   | Expr_not of whenexpr
68   | Expr_add of whenexpr * whenexpr
69   | Expr_sub of whenexpr * whenexpr
70   | Expr_mul of whenexpr * whenexpr
71   | Expr_div of whenexpr * whenexpr
72   | Expr_mod of whenexpr * whenexpr
73   | Expr_changes of string
74   | Expr_increases of string
75   | Expr_decreases of string
76   | Expr_prev of string
77
78 (* This internal type is used during conversion of the OCaml AST
79  * to the whenexpr type.
80  *)
81 type whenexpr_int =
82   | IExpr_bool of bool
83   | IExpr_str of string
84   | IExpr_int of Big_int.big_int
85   | IExpr_float of float
86   | IExpr_var of string
87   | IExpr_app of string * whenexpr_int list
88
89 (* Note that days are not necessarily expressible in seconds (because
90  * of leap seconds), months are not expressible in days (because months
91  * have different lengths), and years are not expressible in days
92  * (because of leap days) although we could save a case here by
93  * expressing years in months.
94  *)
95 type periodexpr =
96   | Every_seconds of int
97   | Every_days of int
98   | Every_months of int
99   | Every_years of int
100
101 type shell_script = {
102   sh_loc : Loc.t;
103   sh_script : string;
104 }
105
106 type variable =
107   | T_bool of bool
108   | T_string of string
109   | T_int of big_int
110   | T_float of float
111
112 let variable_of_rpc = function
113   | `bool_t b -> T_bool b
114   | `string_t s -> T_string s
115   | `int_t i -> T_int (big_int_of_string i)
116   | `float_t f -> T_float f
117
118 let rpc_of_variable = function
119   | T_bool b -> `bool_t b
120   | T_string s -> `string_t s
121   | T_int i -> `int_t (string_of_big_int i)
122   | T_float f -> `float_t f
123
124 type variables = variable StringMap.t
125
126 type job_private = {
127   (* The result of the previous evaluation.  This is used for
128    * implementing edge-triggering, since we only trigger the job to run
129    * when the state changes from false -> true.
130    *)
131   job_prev_eval_state : bool;
132
133   (* When the job {i ran} last time, we take a copy of the variables.
134    * This allows us to implement the 'changes' operator.
135    *)
136   job_prev_variables : variables;
137 }
138
139 let no_job_private =
140   { job_prev_eval_state = false; job_prev_variables = StringMap.empty }
141
142 type job_cond =
143   | When_job of whenexpr
144   | Every_job of periodexpr
145
146 type job = {
147   job_loc : Loc.t;
148   job_name : string;
149   job_cond : job_cond;
150   job_script : shell_script;
151   job_private : job_private;
152 }
153
154 let rec expr_of_ast _loc ast =
155   expr_of_iexpr _loc (iexpr_of_ast _loc ast)
156
157 and iexpr_of_ast _loc = function
158   | ExId (_, IdUid (_, "True")) -> IExpr_bool true
159   | ExId (_, IdUid (_, "False")) -> IExpr_bool false
160   | ExStr (_, str) -> IExpr_str str
161   | ExInt (_, i) -> IExpr_int (big_int_of_string i) (* XXX too large? *)
162   | ExFlo (_, f) -> IExpr_float (float_of_string f)
163   | ExId (_, IdLid (_, id)) -> IExpr_var id
164
165   (* In the OCaml AST, functions are curried right to left, so we
166    * must uncurry to get the list of arguments.
167    *)
168   | ExApp (_, left_tree, right_arg) ->
169     let f, left_args = uncurry_app_tree _loc left_tree in
170     IExpr_app (f, List.rev_map (iexpr_of_ast _loc) (right_arg :: left_args))
171
172   | e ->
173     (* https://groups.google.com/group/fa.caml/browse_thread/thread/f35452d085654bd6 *)
174     eprintf "expr_of_ast: invalid expression: %!";
175     let e = Ast.StExp (_loc, e) in
176     Printers.OCaml.print_implem ~output_file:"/dev/stderr" e;
177
178     invalid_arg (sprintf "%s: invalid expression" (Loc.to_string _loc))
179
180 and uncurry_app_tree _loc = function
181   | ExId (_, IdLid (_, f)) -> f, []
182   | ExApp (_, left_tree, right_arg) ->
183     let f, left_args = uncurry_app_tree _loc left_tree in
184     f, (right_arg :: left_args)
185   | e ->
186     eprintf "uncurry_app_tree: invalid expression: %!";
187     let e = Ast.StExp (_loc, e) in
188     Printers.OCaml.print_implem ~output_file:"/dev/stderr" e;
189
190     invalid_arg (sprintf "%s: invalid expression" (Loc.to_string _loc))
191
192 and expr_of_iexpr _loc = function
193   | IExpr_bool b -> Expr_bool b
194   | IExpr_str s -> Expr_str s
195   | IExpr_int i -> Expr_int i
196   | IExpr_float f -> Expr_float f
197   | IExpr_var v -> Expr_var v
198
199   | IExpr_app ("&&", exprs) ->
200     two_params _loc "&&" exprs (fun e1 e2 -> Expr_and (e1, e2))
201
202   | IExpr_app ("||", exprs) ->
203     two_params _loc "||" exprs (fun e1 e2 -> Expr_or (e1, e2))
204
205   | IExpr_app ("<", exprs) ->
206     two_params _loc "<" exprs (fun e1 e2 -> Expr_lt (e1, e2))
207
208   | IExpr_app ("<=", exprs) ->
209     two_params _loc "<=" exprs (fun e1 e2 -> Expr_le (e1, e2))
210
211   | IExpr_app (("="|"=="), exprs) ->
212     two_params _loc "=" exprs (fun e1 e2 -> Expr_eq (e1, e2))
213
214   | IExpr_app (">=", exprs) ->
215     two_params _loc ">=" exprs (fun e1 e2 -> Expr_ge (e1, e2))
216
217   | IExpr_app (">", exprs) ->
218     two_params _loc ">" exprs (fun e1 e2 -> Expr_gt (e1, e2))
219
220   | IExpr_app ("!", exprs) ->
221     one_param _loc "!" exprs (fun e1 -> Expr_not e1)
222
223   | IExpr_app ("+", exprs) ->
224     two_params _loc "+" exprs (fun e1 e2 -> Expr_add (e1, e2))
225
226   | IExpr_app ("-", exprs) ->
227     two_params _loc "+" exprs (fun e1 e2 -> Expr_sub (e1, e2))
228
229   | IExpr_app ("*", exprs) ->
230     two_params _loc "+" exprs (fun e1 e2 -> Expr_mul (e1, e2))
231
232   | IExpr_app ("/", exprs) ->
233     two_params _loc "+" exprs (fun e1 e2 -> Expr_div (e1, e2))
234
235   | IExpr_app ("mod", exprs) ->
236     two_params _loc "+" exprs (fun e1 e2 -> Expr_mod (e1, e2))
237
238   | IExpr_app (("change"|"changes"|"changed"), [IExpr_var v]) ->
239     Expr_changes v
240
241   | IExpr_app (("inc"|"increase"|"increases"|"increased"), [IExpr_var v]) ->
242     Expr_increases v
243
244   | IExpr_app (("dec"|"decrease"|"decreases"|"decreased"), [IExpr_var v]) ->
245     Expr_decreases v
246
247   | IExpr_app (("prev"|"previous"), [IExpr_var v]) ->
248     Expr_prev v
249
250   | IExpr_app (("change"|"changes"|"changed"|"inc"|"increase"|"increases"|"increased"|"dec"|"decrease"|"decreases"|"decreased"|"prev"|"previous") as op, _) ->
251     invalid_arg (sprintf "%s: '%s' operator must be followed by a variable name"
252                    (Loc.to_string _loc) op)
253
254   | IExpr_app (op, _) ->
255     invalid_arg (sprintf "%s: unknown operator in expression: %s"
256                    (Loc.to_string _loc) op)
257
258 and two_params _loc op exprs f =
259   match exprs with
260   | [e1; e2] -> f (expr_of_iexpr _loc e1) (expr_of_iexpr _loc e2)
261   | _ ->
262     invalid_arg (sprintf "%s: %s operator must be applied to two parameters"
263                    op (Loc.to_string _loc))
264
265 and one_param _loc op exprs f =
266   match exprs with
267   | [e1] -> f (expr_of_iexpr _loc e1)
268   | _ ->
269     invalid_arg (sprintf "%s: %s operator must be applied to one parameter"
270                    op (Loc.to_string _loc))
271
272 let rec string_of_whenexpr = function
273   | Expr_bool b -> sprintf "%b" b
274   | Expr_str s -> sprintf "%S" s
275   | Expr_int i -> sprintf "%s" (string_of_big_int i)
276   | Expr_float f -> sprintf "%f" f
277   | Expr_var v -> sprintf "%s" v
278   | Expr_and (e1, e2) ->
279     sprintf "%s && %s" (string_of_whenexpr e1) (string_of_whenexpr e2)
280   | Expr_or (e1, e2) ->
281     sprintf "%s || %s" (string_of_whenexpr e1) (string_of_whenexpr e2)
282   | Expr_lt (e1, e2) ->
283     sprintf "%s < %s" (string_of_whenexpr e1) (string_of_whenexpr e2)
284   | Expr_le (e1, e2) ->
285     sprintf "%s <= %s" (string_of_whenexpr e1) (string_of_whenexpr e2)
286   | Expr_eq (e1, e2) ->
287     sprintf "%s == %s" (string_of_whenexpr e1) (string_of_whenexpr e2)
288   | Expr_ge (e1, e2) ->
289     sprintf "%s >= %s" (string_of_whenexpr e1) (string_of_whenexpr e2)
290   | Expr_gt (e1, e2) ->
291     sprintf "%s > %s" (string_of_whenexpr e1) (string_of_whenexpr e2)
292   | Expr_not e -> sprintf "! %s" (string_of_whenexpr e)
293   | Expr_add (e1, e2) ->
294     sprintf "%s + %s" (string_of_whenexpr e1) (string_of_whenexpr e2)
295   | Expr_sub (e1, e2) ->
296     sprintf "%s - %s" (string_of_whenexpr e1) (string_of_whenexpr e2)
297   | Expr_mul (e1, e2) ->
298     sprintf "%s * %s" (string_of_whenexpr e1) (string_of_whenexpr e2)
299   | Expr_div (e1, e2) ->
300     sprintf "%s / %s" (string_of_whenexpr e1) (string_of_whenexpr e2)
301   | Expr_mod (e1, e2) ->
302     sprintf "%s mod %s" (string_of_whenexpr e1) (string_of_whenexpr e2)
303   | Expr_changes v -> sprintf "changes %s" v
304   | Expr_increases v -> sprintf "increases %s" v
305   | Expr_decreases v -> sprintf "decreases %s" v
306   | Expr_prev v -> sprintf "prev %s" v
307
308 let string_of_periodexpr = function
309   | Every_seconds 1 -> "1 second"
310   | Every_seconds i -> sprintf "%d seconds" i
311   | Every_days 1 -> "1 day"
312   | Every_days i -> sprintf "%d days" i
313   | Every_months 1 -> "1 month"
314   | Every_months i -> sprintf "%d months" i
315   | Every_years 1 -> "1 year"
316   | Every_years i -> sprintf "%d years" i
317
318 let rec dependencies_of_whenexpr = function
319   | Expr_bool _ -> []
320   | Expr_str _ -> []
321   | Expr_int _ -> []
322   | Expr_float _ -> []
323   | Expr_var v -> [v]
324   | Expr_and (e1, e2)
325   | Expr_or (e1, e2)
326   | Expr_lt (e1, e2)
327   | Expr_le (e1, e2)
328   | Expr_eq (e1, e2)
329   | Expr_ge (e1, e2)
330   | Expr_gt (e1, e2)
331   | Expr_add (e1, e2)
332   | Expr_sub (e1, e2)
333   | Expr_mul (e1, e2)
334   | Expr_div (e1, e2)
335   | Expr_mod (e1, e2) ->
336     dependencies_of_whenexpr e1 @ dependencies_of_whenexpr e2
337   | Expr_not e ->
338     dependencies_of_whenexpr e
339   | Expr_changes v
340   | Expr_increases v
341   | Expr_decreases v
342   | Expr_prev v -> [v]
343
344 let dependencies_of_job = function
345   | { job_cond = When_job whenexpr } -> dependencies_of_whenexpr whenexpr
346   | { job_cond = Every_job _ } -> []
347
348 let rec eval_whenexpr job variables = function
349   | Expr_bool b -> T_bool b
350   | Expr_str s -> T_string s
351   | Expr_int i -> T_int i
352   | Expr_float f -> T_float f
353
354   | Expr_var v ->
355     (try StringMap.find v variables with Not_found -> T_string "")
356
357   | Expr_and (e1, e2) ->
358     if eval_whenexpr_as_bool job variables e1 &&
359        eval_whenexpr_as_bool job variables e2 then
360       T_bool true
361     else
362       T_bool false
363
364   | Expr_or (e1, e2) ->
365     if eval_whenexpr_as_bool job variables e1 ||
366        eval_whenexpr_as_bool job variables e2 then
367       T_bool true
368     else
369       T_bool false
370
371   | Expr_lt (e1, e2) ->
372     let e1 = eval_whenexpr job variables e1
373     and e2 = eval_whenexpr job variables e2 in
374     if compare_values e1 e2 < 0 then
375       T_bool true
376     else
377       T_bool false
378
379   | Expr_le (e1, e2) ->
380     let e1 = eval_whenexpr job variables e1
381     and e2 = eval_whenexpr job variables e2 in
382     if compare_values e1 e2 <= 0 then
383       T_bool true
384     else
385       T_bool false
386
387   | Expr_eq (e1, e2) ->
388     let e1 = eval_whenexpr job variables e1
389     and e2 = eval_whenexpr job variables e2 in
390     if compare_values e1 e2 = 0 then
391       T_bool true
392     else
393       T_bool false
394
395   | Expr_ge (e1, e2) ->
396     let e1 = eval_whenexpr job variables e1
397     and e2 = eval_whenexpr job variables e2 in
398     if compare_values e1 e2 >= 0 then
399       T_bool true
400     else
401       T_bool false
402
403   | Expr_gt (e1, e2) ->
404     let e1 = eval_whenexpr job variables e1
405     and e2 = eval_whenexpr job variables e2 in
406     if compare_values e1 e2 > 0 then
407       T_bool true
408     else
409       T_bool false
410
411   | Expr_not e ->
412     if not (eval_whenexpr_as_bool job variables e) then
413       T_bool true
414     else
415       T_bool false
416
417   | Expr_add (e1, e2) ->
418     let e1 = eval_whenexpr job variables e1
419     and e2 = eval_whenexpr job variables e2 in
420     add_values e1 e2
421
422   | Expr_sub (e1, e2) ->
423     let e1 = eval_whenexpr job variables e1
424     and e2 = eval_whenexpr job variables e2 in
425     sub_values e1 e2
426
427   | Expr_mul (e1, e2) ->
428     let e1 = eval_whenexpr job variables e1
429     and e2 = eval_whenexpr job variables e2 in
430     mul_values e1 e2
431
432   | Expr_div (e1, e2) ->
433     let e1 = eval_whenexpr job variables e1
434     and e2 = eval_whenexpr job variables e2 in
435     div_values e1 e2
436
437   | Expr_mod (e1, e2) ->
438     let e1 = eval_whenexpr job variables e1
439     and e2 = eval_whenexpr job variables e2 in
440     mod_values e1 e2
441
442   | Expr_changes v ->
443     let prev_value, curr_value = get_prev_curr_value job variables v in
444     if compare_values prev_value curr_value <> 0 then
445       T_bool true
446     else
447       T_bool false
448
449   | Expr_increases v ->
450     let prev_value, curr_value = get_prev_curr_value job variables v in
451     if compare_values prev_value curr_value > 0 then
452       T_bool true
453     else
454       T_bool false
455
456   | Expr_decreases v ->
457     let prev_value, curr_value = get_prev_curr_value job variables v in
458     if compare_values prev_value curr_value < 0 then
459       T_bool true
460     else
461       T_bool false
462
463   | Expr_prev v ->
464     try StringMap.find v job.job_private.job_prev_variables
465     with Not_found -> T_string ""
466
467 and get_prev_curr_value job variables v =
468   let prev_value =
469     try StringMap.find v job.job_private.job_prev_variables
470     with Not_found -> T_string "" in
471   let curr_value =
472     try StringMap.find v variables
473     with Not_found -> T_string "" in
474   prev_value, curr_value
475
476 (* Call {!eval_whenexpr} and cast the result to a boolean. *)
477 and eval_whenexpr_as_bool job variables expr =
478   match eval_whenexpr job variables expr with
479   | T_bool r -> r
480   | T_string s -> s <> ""
481   | T_int i -> sign_big_int i <> 0
482   | T_float f -> f <> 0.
483
484 (* Do a comparison on two typed values and return -1/0/+1.  If the
485  * types are different then we compare the values as strings.  The user
486  * can avoid this by specifying types.
487  *)
488 and compare_values value1 value2 =
489   match value1, value2 with
490   | T_bool b1, T_bool b2 -> compare b1 b2
491   | T_string s1, T_string s2 -> compare s1 s2
492   | T_int i1, T_int i2 -> compare_big_int i1 i2
493   | T_float f1, T_float f2 -> compare f1 f2
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_bool b -> string_of_bool b
563   | T_string s -> s
564   | T_int i -> string_of_big_int i
565   | T_float f -> string_of_float f
566
567 and printable_string_of_variable = function
568   | T_bool b -> string_of_bool b
569   | T_string s -> sprintf "%S" s
570   | T_int i -> string_of_big_int i
571   | T_float f -> string_of_float f
572
573 let job_evaluate job variables =
574   match job with
575   | { job_cond = Every_job _ } -> false, job
576   | { job_cond = When_job whenexpr } ->
577     let state = eval_whenexpr_as_bool job variables whenexpr in
578
579     (* Because jobs are edge-triggered, we're only interested in the
580      * case where the evaluation state changes from false -> true.
581      *)
582     match job.job_private.job_prev_eval_state, state with
583     | false, false
584     | true, true
585     | true, false ->
586       let jobp = { job.job_private with job_prev_eval_state = state } in
587       let job = { job with job_private = jobp } in
588       false, job
589
590     | false, true ->
591       let jobp = { job_prev_eval_state = true;
592                    job_prev_variables = variables } in
593       let job = { job with job_private = jobp } in
594       true, job
595
596 let next_periodexpr =
597   (* Round up 'a' to the next multiple of 'i'. *)
598   let round_up_float a i =
599     let r = mod_float a i in
600     if r = 0. then a +. i else a +. (i -. r)
601   and round_up a i =
602     let r = a mod i in
603     if r = 0 then a + i else a + (i - r)
604   in
605
606   fun t -> function
607   | Every_seconds i ->
608     let i = float_of_int i in
609     round_up_float t i
610
611   | Every_years i ->
612     let tm = gmtime t in
613
614     (* Round 'tm' up to the first day of the next year. *)
615     let year = round_up tm.tm_year i in
616     let tm = { tm with tm_sec = 0; tm_min = 0; tm_hour = 0;
617                        tm_mday = 1; tm_mon = 0; tm_year = year } in
618     fst (mktime tm)
619
620   | Every_days i ->
621     let t = Date.from_unixfloat t in
622     let t0 = Date.make 1970 1 1 in
623
624     (* Number of whole days since Unix Epoch. *)
625     let nb_days = Date.Period.safe_nb_days (Date.sub t t0) in
626
627     let nb_days = round_up nb_days i in
628     let t' = Date.add t0 (Date.Period.day nb_days) in
629     Date.to_unixfloat t'
630
631   | Every_months i ->
632     (* Calculate number of whole months since Unix Epoch. *)
633     let tm = gmtime t in
634     let months = 12 * (tm.tm_year - 70) + tm.tm_mon in
635
636     let months = round_up months i in
637     let t0 = Date.make 1970 1 1 in
638     let t' = Date.add t0 (Date.Period.month months) in
639     Date.to_unixfloat t'