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