Scheduling of every-jobs.
[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 StringSet = Set.Make (String)
35
36 let rec filter_map f = function
37   | [] -> []
38   | x :: xs ->
39     match f x with
40     | Some y -> y :: filter_map f xs
41     | None -> filter_map f xs
42
43 type whenexpr =
44   | Expr_bool of bool
45   | Expr_str of string
46   | Expr_int of Big_int.big_int
47   | Expr_float of float
48   | Expr_var of string
49   | Expr_and of whenexpr * whenexpr
50   | Expr_or of whenexpr * whenexpr
51   | Expr_eq of whenexpr * whenexpr
52   | Expr_not of whenexpr
53   | Expr_changes of string
54
55 (* This internal type is used during conversion of the OCaml AST
56  * to the whenexpr type.
57  *)
58 type whenexpr_int =
59   | IExpr_bool of bool
60   | IExpr_str of string
61   | IExpr_int of Big_int.big_int
62   | IExpr_float of float
63   | IExpr_var of string
64   | IExpr_app of string * whenexpr_int list
65
66 (* Note that days are not necessarily expressible in seconds (because
67  * of leap seconds), months are not expressible in days (because months
68  * have different lengths), and years are not expressible in days
69  * (because of leap days) although we could save a case here by
70  * expressing years in months.
71  *)
72 type periodexpr =
73   | Every_seconds of int
74   | Every_days of int
75   | Every_months of int
76   | Every_years of int
77
78 type shell_script = {
79   sh_loc : Loc.t;
80   sh_script : string;
81 }
82
83 type variable =
84   | T_bool of bool
85   | T_string of string
86   | T_int of big_int
87   | T_float of float
88
89 let variable_of_rpc = function
90   | `bool_t b -> T_bool b
91   | `string_t s -> T_string s
92   | `int_t i -> T_int (big_int_of_string i)
93   | `float_t f -> T_float f
94
95 let rpc_of_variable = function
96   | T_bool b -> `bool_t b
97   | T_string s -> `string_t s
98   | T_int i -> `int_t (string_of_big_int i)
99   | T_float f -> `float_t f
100
101 type variables = variable StringMap.t
102
103 type job_private = {
104   (* The result of the previous evaluation.  This is used for
105    * implementing edge-triggering, since we only trigger the job to run
106    * when the state changes from false -> true.
107    *)
108   job_prev_eval_state : bool;
109
110   (* When the job {i ran} last time, we take a copy of the variables.
111    * This allows us to implement the 'changes' operator.
112    *)
113   job_prev_variables : variables;
114 }
115
116 let no_job_private =
117   { job_prev_eval_state = false; job_prev_variables = StringMap.empty }
118
119 type job_cond =
120   | When_job of whenexpr
121   | Every_job of periodexpr
122
123 type job = {
124   job_loc : Loc.t;
125   job_name : string;
126   job_cond : job_cond;
127   job_script : shell_script;
128   job_private : job_private;
129 }
130
131 let rec expr_of_ast _loc ast =
132   expr_of_iexpr _loc (iexpr_of_ast _loc ast)
133
134 and iexpr_of_ast _loc = function
135   | ExId (_, IdLid (_, "true")) -> IExpr_bool true
136   | ExId (_, IdLid (_, "false")) -> IExpr_bool false
137   | ExStr (_, str) -> IExpr_str str
138   | ExInt (_, i) -> IExpr_int (big_int_of_string i) (* XXX too large? *)
139   | ExFlo (_, f) -> IExpr_float (float_of_string f)
140   | ExId (_, IdLid (_, id)) -> IExpr_var id
141
142   (* In the OCaml AST, functions are curried right to left, so we
143    * must uncurry to get the list of arguments.
144    *)
145   | ExApp (_, left_tree, right_arg) ->
146     let f, left_args = uncurry_app_tree _loc left_tree in
147     IExpr_app (f, List.rev_map (iexpr_of_ast _loc) (right_arg :: left_args))
148
149   | e ->
150     (* https://groups.google.com/group/fa.caml/browse_thread/thread/f35452d085654bd6 *)
151     eprintf "expr_of_ast: invalid expression: %!";
152     let e = Ast.StExp (_loc, e) in
153     Printers.OCaml.print_implem ~output_file:"/dev/stderr" e;
154
155     invalid_arg (sprintf "%s: invalid expression" (Loc.to_string _loc))
156
157 and uncurry_app_tree _loc = function
158   | ExId (_, IdLid (_, f)) -> f, []
159   | ExApp (_, left_tree, right_arg) ->
160     let f, left_args = uncurry_app_tree _loc left_tree in
161     f, (right_arg :: left_args)
162   | e ->
163     eprintf "uncurry_app_tree: invalid expression: %!";
164     let e = Ast.StExp (_loc, e) in
165     Printers.OCaml.print_implem ~output_file:"/dev/stderr" e;
166
167     invalid_arg (sprintf "%s: invalid expression" (Loc.to_string _loc))
168
169 and expr_of_iexpr _loc = function
170   | IExpr_bool b -> Expr_bool b
171   | IExpr_str s -> Expr_str s
172   | IExpr_int i -> Expr_int i
173   | IExpr_float f -> Expr_float f
174   | IExpr_var v -> Expr_var v
175
176   | IExpr_app ("&&", exprs) ->
177     (match exprs with
178     | [e1; e2] -> Expr_and (expr_of_iexpr _loc e1, expr_of_iexpr _loc e2)
179     | _ ->
180       invalid_arg (sprintf "%s: && operator must be applied to two parameters"
181                      (Loc.to_string _loc))
182     )
183
184   | IExpr_app ("||", exprs) ->
185     (match exprs with
186     | [e1; e2] -> Expr_or (expr_of_iexpr _loc e1, expr_of_iexpr _loc e2)
187     | _ ->
188       invalid_arg (sprintf "%s: || operator must be applied to two parameters"
189                       (Loc.to_string _loc))
190     )
191
192   | IExpr_app (("="|"=="), exprs) ->
193     (match exprs with
194     | [e1; e2] -> Expr_eq (expr_of_iexpr _loc e1, expr_of_iexpr _loc e2)
195     | _ ->
196       invalid_arg (sprintf "%s: = operator must be applied to two parameters"
197                       (Loc.to_string _loc))
198     )
199
200   | IExpr_app ("!", exprs) ->
201     (match exprs with
202     | [e1] -> Expr_not (expr_of_iexpr _loc e1)
203     | _ ->
204       invalid_arg (sprintf "%s: ! operator must be applied to one parameter"
205                       (Loc.to_string _loc))
206     )
207
208   | IExpr_app (("change"|"changes"|"changed"), [IExpr_var v]) ->
209     Expr_changes v
210
211   | IExpr_app (("change"|"changes"|"changed"), _) ->
212     invalid_arg (sprintf "%s: 'changes' operator must be followed by a variable name"
213                     (Loc.to_string _loc))
214
215   | IExpr_app (op, _) ->
216     invalid_arg (sprintf "%s: unknown operator in expression: %s"
217                    (Loc.to_string _loc) op)
218
219 let rec string_of_whenexpr = function
220   | Expr_bool b -> sprintf "%b" b
221   | Expr_str s -> sprintf "%S" s
222   | Expr_int i -> sprintf "%s" (string_of_big_int i)
223   | Expr_float f -> sprintf "%f" f
224   | Expr_var v -> sprintf "%s" v
225   | Expr_and (e1, e2) ->
226     sprintf "%s && %s" (string_of_whenexpr e1) (string_of_whenexpr e2)
227   | Expr_or (e1, e2) ->
228     sprintf "%s || %s" (string_of_whenexpr e1) (string_of_whenexpr e2)
229   | Expr_eq (e1, e2) ->
230     sprintf "%s == %s" (string_of_whenexpr e1) (string_of_whenexpr e2)
231   | Expr_not e -> sprintf "! %s" (string_of_whenexpr e)
232   | Expr_changes v -> sprintf "changes %s" v
233
234 let string_of_periodexpr = function
235   | Every_seconds 1 -> "1 second"
236   | Every_seconds i -> sprintf "%d seconds" i
237   | Every_days 1 -> "1 day"
238   | Every_days i -> sprintf "%d days" i
239   | Every_months 1 -> "1 month"
240   | Every_months i -> sprintf "%d months" i
241   | Every_years 1 -> "1 year"
242   | Every_years i -> sprintf "%d years" i
243
244 let rec dependencies_of_whenexpr = function
245   | Expr_bool _ -> []
246   | Expr_str _ -> []
247   | Expr_int _ -> []
248   | Expr_float _ -> []
249   | Expr_var v -> [v]
250   | Expr_and (e1, e2) ->
251     dependencies_of_whenexpr e1 @ dependencies_of_whenexpr e2
252   | Expr_or (e1, e2) ->
253     dependencies_of_whenexpr e1 @ dependencies_of_whenexpr e2
254   | Expr_eq (e1, e2) ->
255     dependencies_of_whenexpr e1 @ dependencies_of_whenexpr e2
256   | Expr_not e -> dependencies_of_whenexpr e
257   | Expr_changes v -> [v]
258
259 let dependencies_of_job = function
260   | { job_cond = When_job whenexpr } -> dependencies_of_whenexpr whenexpr
261   | { job_cond = Every_job _ } -> []
262
263 let rec eval_whenexpr job variables = function
264   | Expr_bool b -> T_bool b
265   | Expr_str s -> T_string s
266   | Expr_int i -> T_int i
267   | Expr_float f -> T_float f
268
269   | Expr_var v ->
270     (try StringMap.find v variables with Not_found -> T_string "")
271
272   | Expr_and (e1, e2) ->
273     if eval_whenexpr_as_bool job variables e1 &&
274        eval_whenexpr_as_bool job variables e2 then
275       T_bool true
276     else
277       T_bool false
278
279   | Expr_or (e1, e2) ->
280     if eval_whenexpr_as_bool job variables e1 ||
281        eval_whenexpr_as_bool job variables e2 then
282       T_bool true
283     else
284       T_bool false
285
286   | Expr_eq (e1, e2) ->
287     let e1 = eval_whenexpr job variables e1
288     and e2 = eval_whenexpr job variables e2 in
289     if 0 = compare_values e1 e2 then
290       T_bool true
291     else
292       T_bool false
293
294   | Expr_not e ->
295     if not (eval_whenexpr_as_bool job variables e) then
296       T_bool true
297     else
298       T_bool false
299
300   | Expr_changes v ->
301     let prev_value =
302       try StringMap.find v job.job_private.job_prev_variables
303       with Not_found -> T_string "" in
304     let curr_value =
305       try StringMap.find v variables
306       with Not_found -> T_string "" in
307
308     if 0 <> compare_values prev_value curr_value then
309       T_bool true
310     else
311       T_bool false
312
313 (* Call {!eval_whenexpr} and cast the result to a boolean. *)
314 and eval_whenexpr_as_bool job variables expr =
315   match eval_whenexpr job variables expr with
316   | T_bool r -> r
317   | T_string s -> s <> ""
318   | T_int i -> sign_big_int i <> 0
319   | T_float f -> f <> 0.
320
321 (* Do a comparison on two typed values and return -1/0/+1.  If the
322  * types are different then we compare the values as strings.  The user
323  * can avoid this by specifying types.
324  *)
325 and compare_values value1 value2 =
326   match value1, value2 with
327   | T_bool b1, T_bool b2 -> compare b1 b2
328   | T_string s1, T_string s2 -> compare s1 s2
329   | T_int i1, T_int i2 -> compare_big_int i1 i2
330   | T_float f1, T_float f2 -> compare f1 f2
331   | _ ->
332     let value1 = value_as_string value1
333     and value2 = value_as_string value2 in
334     compare value1 value2
335
336 and value_as_string = function
337   | T_bool b -> string_of_bool b
338   | T_string s -> s
339   | T_int i -> string_of_big_int i
340   | T_float f -> string_of_float f
341
342 let job_evaluate job variables =
343   match job with
344   | { job_cond = Every_job _ } -> false, job
345   | { job_cond = When_job whenexpr } ->
346     let state = eval_whenexpr_as_bool job variables whenexpr in
347
348     (* Because jobs are edge-triggered, we're only interested in the
349      * case where the evaluation state changes from false -> true.
350      *)
351     match job.job_private.job_prev_eval_state, state with
352     | false, false
353     | true, true
354     | true, false ->
355       let jobp = { job.job_private with job_prev_eval_state = state } in
356       let job = { job with job_private = jobp } in
357       false, job
358
359     | false, true ->
360       let jobp = { job_prev_eval_state = true;
361                    job_prev_variables = variables } in
362       let job = { job with job_private = jobp } in
363       true, job
364
365 let next_periodexpr =
366   (* Round up 'a' to the next multiple of 'i'. *)
367   let round_up_float a i =
368     let r = mod_float a i in
369     if r = 0. then a +. i else a +. (i -. r)
370   and round_up a i =
371     let r = a mod i in
372     if r = 0 then a + i else a + (i - r)
373   in
374
375   fun t -> function
376   | Every_seconds i ->
377     let i = float_of_int i in
378     round_up_float t i
379
380   | Every_years i ->
381     let tm = gmtime t in
382
383     (* Round 'tm' up to the first day of the next year. *)
384     let year = round_up tm.tm_year i in
385     let tm = { tm with tm_sec = 0; tm_min = 0; tm_hour = 0;
386                        tm_mday = 1; tm_mon = 0; tm_year = year } in
387     fst (mktime tm)
388
389   | Every_days i ->
390     let t = Date.from_unixfloat t in
391     let t0 = Date.make 1970 1 1 in
392
393     (* Number of whole days since Unix Epoch. *)
394     let nb_days = Date.Period.safe_nb_days (Date.sub t t0) in
395
396     let nb_days = round_up nb_days i in
397     let t' = Date.add t0 (Date.Period.day nb_days) in
398     Date.to_unixfloat t'
399
400   | Every_months i ->
401     (* Calculate number of whole months since Unix Epoch. *)
402     let tm = gmtime t in
403     let months = 12 * (tm.tm_year - 70) + tm.tm_mon in
404
405     let months = round_up months i in
406     let t0 = Date.make 1970 1 1 in
407     let t' = Date.add t0 (Date.Period.month months) in
408     Date.to_unixfloat t'