1fbb1c61c6dfcd864a6e17a37bbe46a2f78c9aaa
[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 Big_int
23 open Printf
24
25 module StringMap = struct
26   include Map.Make (String)
27   let keys m = fold (fun k _ ks -> k :: ks) m []
28   let values m = fold (fun _ v vs -> v :: vs) m []
29 end
30
31 module StringSet = Set.Make (String)
32
33 type whenexpr =
34   | Expr_bool of bool
35   | Expr_str of string
36   | Expr_int of Big_int.big_int
37   | Expr_float of float
38   | Expr_var of string
39   | Expr_and of whenexpr * whenexpr
40   | Expr_or of whenexpr * whenexpr
41   | Expr_eq of whenexpr * whenexpr
42   | Expr_not of whenexpr
43   | Expr_changes of string
44
45 (* This internal type is used during conversion of the OCaml AST
46  * to the whenexpr type.
47  *)
48 type whenexpr_int =
49   | IExpr_bool of bool
50   | IExpr_str of string
51   | IExpr_int of Big_int.big_int
52   | IExpr_float of float
53   | IExpr_var of string
54   | IExpr_app of string * whenexpr_int list
55
56 (* Note that days are not necessarily expressible in seconds (because
57  * of leap seconds), months are not expressible in days (because months
58  * have different lengths), and years are not expressible in days
59  * (because of leap days) although we could save a case here by
60  * expressing years in months.
61  *)
62 type periodexpr =
63   | Every_seconds of int
64   | Every_days of int
65   | Every_months of int
66   | Every_years of int
67
68 type shell_script = {
69   sh_loc : Loc.t;
70   sh_script : string;
71 }
72
73 type variable =
74   | T_bool of bool
75   | T_string of string
76   | T_int of big_int
77   | T_float of float
78
79 let variable_of_rpc = function
80   | `bool_t b -> T_bool b
81   | `string_t s -> T_string s
82   | `int_t i -> T_int (big_int_of_string i)
83   | `float_t f -> T_float f
84
85 let rpc_of_variable = function
86   | T_bool b -> `bool_t b
87   | T_string s -> `string_t s
88   | T_int i -> `int_t (string_of_big_int i)
89   | T_float f -> `float_t f
90
91 type variables = variable StringMap.t
92
93 type job_private = {
94   (* The result of the previous evaluation.  This is used for
95    * implementing edge-triggering, since we only trigger the job to run
96    * when the state changes from false -> true.
97    *)
98   job_prev_eval_state : bool;
99
100   (* When the job {i ran} last time, we take a copy of the variables.
101    * This allows us to implement the 'changes' operator.
102    *)
103   job_prev_variables : variables;
104 }
105
106 let no_job_private =
107   { job_prev_eval_state = false; job_prev_variables = StringMap.empty }
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   job_private : job_private;
119 }
120
121 let rec expr_of_ast _loc ast =
122   expr_of_iexpr _loc (iexpr_of_ast _loc ast)
123
124 and iexpr_of_ast _loc = function
125   | ExId (_, IdLid (_, "true")) -> IExpr_bool true
126   | ExId (_, IdLid (_, "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_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     (match exprs with
168     | [e1; e2] -> Expr_and (expr_of_iexpr _loc e1, expr_of_iexpr _loc e2)
169     | _ ->
170       invalid_arg (sprintf "%s: && operator must be applied to two parameters"
171                      (Loc.to_string _loc))
172     )
173
174   | IExpr_app ("||", exprs) ->
175     (match exprs with
176     | [e1; e2] -> Expr_or (expr_of_iexpr _loc e1, expr_of_iexpr _loc e2)
177     | _ ->
178       invalid_arg (sprintf "%s: || operator must be applied to two parameters"
179                       (Loc.to_string _loc))
180     )
181
182   | IExpr_app (("="|"=="), exprs) ->
183     (match exprs with
184     | [e1; e2] -> Expr_eq (expr_of_iexpr _loc e1, expr_of_iexpr _loc e2)
185     | _ ->
186       invalid_arg (sprintf "%s: = operator must be applied to two parameters"
187                       (Loc.to_string _loc))
188     )
189
190   | IExpr_app ("!", exprs) ->
191     (match exprs with
192     | [e1] -> Expr_not (expr_of_iexpr _loc e1)
193     | _ ->
194       invalid_arg (sprintf "%s: ! operator must be applied to one parameter"
195                       (Loc.to_string _loc))
196     )
197
198   | IExpr_app (("change"|"changes"|"changed"), [IExpr_var v]) ->
199     Expr_changes v
200
201   | IExpr_app (("change"|"changes"|"changed"), _) ->
202     invalid_arg (sprintf "%s: 'changes' operator must be followed by a variable name"
203                     (Loc.to_string _loc))
204
205   | IExpr_app (op, _) ->
206     invalid_arg (sprintf "%s: unknown operator in expression: %s"
207                    (Loc.to_string _loc) op)
208
209 let rec string_of_whenexpr = function
210   | Expr_bool b -> sprintf "%b" b
211   | Expr_str s -> sprintf "%S" s
212   | Expr_int i -> sprintf "%s" (string_of_big_int i)
213   | Expr_float f -> sprintf "%f" f
214   | Expr_var v -> sprintf "%s" v
215   | Expr_and (e1, e2) ->
216     sprintf "%s && %s" (string_of_whenexpr e1) (string_of_whenexpr e2)
217   | Expr_or (e1, e2) ->
218     sprintf "%s || %s" (string_of_whenexpr e1) (string_of_whenexpr e2)
219   | Expr_eq (e1, e2) ->
220     sprintf "%s == %s" (string_of_whenexpr e1) (string_of_whenexpr e2)
221   | Expr_not e -> sprintf "! %s" (string_of_whenexpr e)
222   | Expr_changes v -> sprintf "changes %s" v
223
224 let string_of_periodexpr = function
225   | Every_seconds 1 -> "1 second"
226   | Every_seconds i -> sprintf "%d seconds" i
227   | Every_days 1 -> "1 day"
228   | Every_days i -> sprintf "%d days" i
229   | Every_months 1 -> "1 month"
230   | Every_months i -> sprintf "%d months" i
231   | Every_years 1 -> "1 year"
232   | Every_years i -> sprintf "%d years" i
233
234 let rec dependencies_of_whenexpr = function
235   | Expr_bool _ -> []
236   | Expr_str _ -> []
237   | Expr_int _ -> []
238   | Expr_float _ -> []
239   | Expr_var v -> [v]
240   | Expr_and (e1, e2) ->
241     dependencies_of_whenexpr e1 @ dependencies_of_whenexpr e2
242   | Expr_or (e1, e2) ->
243     dependencies_of_whenexpr e1 @ dependencies_of_whenexpr e2
244   | Expr_eq (e1, e2) ->
245     dependencies_of_whenexpr e1 @ dependencies_of_whenexpr e2
246   | Expr_not e -> dependencies_of_whenexpr e
247   | Expr_changes v -> [v]
248
249 let dependencies_of_job = function
250   | { job_cond = When_job whenexpr } -> dependencies_of_whenexpr whenexpr
251   | { job_cond = Every_job _ } -> []
252
253 let rec eval_whenexpr job variables = function
254   | Expr_bool b -> T_bool b
255   | Expr_str s -> T_string s
256   | Expr_int i -> T_int i
257   | Expr_float f -> T_float f
258
259   | Expr_var v ->
260     (try StringMap.find v variables with Not_found -> T_string "")
261
262   | Expr_and (e1, e2) ->
263     if eval_whenexpr_as_bool job variables e1 &&
264        eval_whenexpr_as_bool job variables e2 then
265       T_bool true
266     else
267       T_bool false
268
269   | Expr_or (e1, e2) ->
270     if eval_whenexpr_as_bool job variables e1 ||
271        eval_whenexpr_as_bool job variables e2 then
272       T_bool true
273     else
274       T_bool false
275
276   | Expr_eq (e1, e2) ->
277     let e1 = eval_whenexpr job variables e1
278     and e2 = eval_whenexpr job variables e2 in
279     if 0 = compare_values e1 e2 then
280       T_bool true
281     else
282       T_bool false
283
284   | Expr_not e ->
285     if not (eval_whenexpr_as_bool job variables e) then
286       T_bool true
287     else
288       T_bool false
289
290   | Expr_changes v ->
291     let prev_value =
292       try StringMap.find v job.job_private.job_prev_variables
293       with Not_found -> T_string "" in
294     let curr_value =
295       try StringMap.find v variables
296       with Not_found -> T_string "" in
297
298     if 0 <> compare_values prev_value curr_value then
299       T_bool true
300     else
301       T_bool false
302
303 (* Call {!eval_whenexpr} and cast the result to a boolean. *)
304 and eval_whenexpr_as_bool job variables expr =
305   match eval_whenexpr job variables expr with
306   | T_bool r -> r
307   | T_string s -> s <> ""
308   | T_int i -> sign_big_int i <> 0
309   | T_float f -> f <> 0.
310
311 (* Do a comparison on two typed values and return -1/0/+1.  If the
312  * types are different then we compare the values as strings.  The user
313  * can avoid this by specifying types.
314  *)
315 and compare_values value1 value2 =
316   match value1, value2 with
317   | T_bool b1, T_bool b2 -> compare b1 b2
318   | T_string s1, T_string s2 -> compare s1 s2
319   | T_int i1, T_int i2 -> compare_big_int i1 i2
320   | T_float f1, T_float f2 -> compare f1 f2
321   | _ ->
322     let value1 = value_as_string value1
323     and value2 = value_as_string value2 in
324     compare value1 value2
325
326 and value_as_string = function
327   | T_bool b -> string_of_bool b
328   | T_string s -> s
329   | T_int i -> string_of_big_int i
330   | T_float f -> string_of_float f
331
332 let job_evaluate job variables =
333   match job with
334   | { job_cond = Every_job _ } -> false, job
335   | { job_cond = When_job whenexpr } ->
336     let state = eval_whenexpr_as_bool job variables whenexpr in
337
338     (* Because jobs are edge-triggered, we're only interested in the
339      * case where the evaluation state changes from false -> true.
340      *)
341     match job.job_private.job_prev_eval_state, state with
342     | false, false
343     | true, true
344     | true, false ->
345       let jobp = { job.job_private with job_prev_eval_state = state } in
346       let job = { job with job_private = jobp } in
347       false, job
348
349     | false, true ->
350       let jobp = { job_prev_eval_state = true;
351                    job_prev_variables = variables } in
352       let job = { job with job_private = jobp } in
353       true, job