Further improve the jit.
[tatoo.git] / src / run.ml
1 (***********************************************************************)
2 (*                                                                     *)
3 (*                               TAToo                                 *)
4 (*                                                                     *)
5 (*                     Kim Nguyen, LRI UMR8623                         *)
6 (*                   Université Paris-Sud & CNRS                       *)
7 (*                                                                     *)
8 (*  Copyright 2010-2013 Université Paris-Sud and Centre National de la *)
9 (*  Recherche Scientifique. All rights reserved.  This file is         *)
10 (*  distributed under the terms of the GNU Lesser General Public       *)
11 (*  License, with the special exception on linking described in file   *)
12 (*  ../LICENSE.                                                        *)
13 (*                                                                     *)
14 (***********************************************************************)
15
16 INCLUDE "utils.ml"
17 INCLUDE "debug.ml"
18
19 open Format
20 open Misc
21
22 type stats = { mutable pass : int;
23                tree_size : int;
24                mutable fetch_trans_cache_access : int;
25                mutable fetch_trans_cache_miss : int;
26                mutable eval_trans_cache_access : int;
27                mutable eval_trans_cache_miss : int;
28                mutable nodes_per_run : int list;
29              }
30
31
32 let dummy_set = StateSet.singleton State.dummy_state
33
34
35
36   IFDEF HTMLTRACE
37   THEN
38 type sat_array = StateSet.t array list
39   DEFINE IFHTML(a,b) = (a)
40   ELSE
41 type sat_array = StateSet.t array
42   DEFINE IFHTML(a,b) = (b)
43   END
44
45 let unsafe_get a i =
46   if i < 0 then StateSet.empty else
47     Array.unsafe_get (IFHTML(List.hd a, a)) i
48
49 let unsafe_set a i v  =
50   (* if v != old_v then *)
51     Array.unsafe_set (IFHTML(List.hd a, a)) i v
52
53 type 'node td_action = 'node -> int -> 'node -> 'node -> StateSet.t
54 type 'node bu_action = 'node -> int -> StateSet.t
55 let dummy_action = fun _ _ -> assert false
56
57 type ('tree, 'node) run = {
58   tree : 'tree ;
59      (* The argument of the run *)
60   auto : Ata.t;
61      (* The automaton to be run *)
62   mutable sat: sat_array;
63      (* A mapping from node preorders to states satisfied at that node *)
64   mutable pass : int;
65      (* Number of run we have performed *)
66   mutable fetch_trans_cache : Ata.Formula.t Cache.N2.t;
67      (* A cache from states * label to list of transitions *)
68   mutable td_cache : 'node td_action Cache.N6.t;
69   mutable bu_cache : 'node bu_action Cache.N6.t;
70      (* Two 6-way caches used during the top-down and bottom-up phase
71         label * self-set * fc-set * ns-set * parent-set * node-shape -> self-set
72      *)
73   stats : stats;
74 }
75
76 let dummy_form = Ata.Formula.stay State.dummy_state
77
78 let get_form run tag (q : State.t) =
79   let auto = run.auto in
80   let fetch_trans_cache = run.fetch_trans_cache in
81   let stats = run.stats in
82   let phi =
83     stats.fetch_trans_cache_access <- stats.fetch_trans_cache_access + 1;
84     Cache.N2.find fetch_trans_cache (tag.QName.id :> int) (q :> int)
85   in
86   if phi == dummy_form then
87     let phi = Ata.get_form auto tag q in
88     let () =
89       stats.fetch_trans_cache_miss <- stats.fetch_trans_cache_miss + 1;
90       Cache.N2.add
91         fetch_trans_cache
92         (tag.QName.id :> int)
93         (q :> int) phi
94     in phi
95   else
96     phi
97
98
99
100 let eval_form phi fcs nss ps ss summary =
101   let open Ata in
102   let rec loop phi =
103     begin match Formula.expr phi with
104     | Boolean.False -> false
105     | Boolean.True -> true
106     | Boolean.Atom (a, b) ->
107       begin
108         let open Tree.NodeSummary in
109         match a.Atom.node with
110         | Move (m, q) ->
111           b && StateSet.mem q (
112             match m with
113               `First_child -> fcs
114             | `Next_sibling -> nss
115             | `Parent | `Previous_sibling -> ps
116             | `Stay -> ss
117           )
118         | Is_first_child -> b == is_left summary
119         | Is_next_sibling -> b == is_right summary
120         | Is k -> b == (k == kind summary)
121         | Has_first_child -> b == has_left summary
122         | Has_next_sibling -> b == has_right summary
123       end
124     | Boolean.And(phi1, phi2) -> loop phi1 && loop phi2
125     | Boolean.Or (phi1, phi2) -> loop phi1 || loop phi2
126     end
127   in
128   loop phi
129
130
131 let eval_trans_aux run tag summary fcs nss ps sat todo  =
132   StateSet.fold (fun q (a_sat) ->
133     let phi =
134       get_form run tag q
135     in
136     if eval_form phi fcs nss ps a_sat summary then
137       StateSet.add q a_sat
138     else a_sat
139   ) todo sat
140
141
142 let rec eval_trans_fix run tag summary fcs nss ps sat todo  =
143   let new_sat =
144     eval_trans_aux run tag summary fcs nss ps sat todo
145   in
146   if new_sat == sat then sat else
147     eval_trans_fix run tag summary fcs nss ps new_sat todo
148
149
150 let eval_trans run trans_cache tag summary fcs nss ps ss todo action_builder =
151   let stats = run.stats in
152   let fcsid = (fcs.StateSet.id :> int) in
153   let nssid = (nss.StateSet.id :> int) in
154   let psid = (ps.StateSet.id :> int) in
155   let ssid = (ss.StateSet.id :> int) in
156   let tagid = (tag.QName.id :> int) in
157
158   let res = Cache.N6.find trans_cache tagid summary ssid fcsid nssid psid in
159   stats.eval_trans_cache_access <- 1 + stats.eval_trans_cache_access;
160   if res != dummy_action then
161     res
162   else
163     let new_sat =
164       eval_trans_fix run tag summary fcs nss ps ss todo
165     in
166     stats.eval_trans_cache_miss <- 1 + stats.eval_trans_cache_miss;
167     let new_action = action_builder ps summary tag new_sat in
168     Cache.N6.add trans_cache tagid summary ssid fcsid nssid psid new_action;
169     new_action
170
171 module NodeSummary = Tree.NodeSummary
172 module Make (T : Tree.S)  =
173 struct
174   module Tree : Tree.S with type node = T.node = T
175   module ResultSet : Deque.S with type elem = Tree.node =
176     Deque.Make (struct type t = Tree.node end)
177
178
179   let make auto tree =
180     let len = Tree.size tree in
181     {
182       tree = tree;
183       auto = auto;
184       sat = (let a = Array.make len StateSet.empty in
185              IFHTML([a], a));
186       pass = 0;
187       fetch_trans_cache = Cache.N2.create dummy_form;
188       td_cache = Cache.N6.create dummy_action;
189       bu_cache = Cache.N6.create dummy_action;
190       stats = {
191         pass = 0;
192         tree_size = len;
193         fetch_trans_cache_access = 0;
194         fetch_trans_cache_miss = 0;
195         eval_trans_cache_access = 0;
196         eval_trans_cache_miss = 0;
197         nodes_per_run = [];
198       }
199     }
200
201
202   let top_down run mk_update_res =
203     let num_visited = ref 0 in
204     let i = run.pass in
205     let tree = run.tree in
206     let auto = run.auto in
207     let states_by_rank = Ata.get_states_by_rank auto in
208     let td_todo = states_by_rank.(i) in
209     let bu_todo =
210       if i == Array.length states_by_rank - 1 then StateSet.empty
211       else
212         states_by_rank.(i+1)
213     in
214     let run_sat = run.sat in
215     let last_run = i >= Array.length states_by_rank - 2 in
216
217     let rec common node parent parent_sat action_builder =
218       begin
219         incr num_visited;
220         let tag = Tree.tag tree node in
221         let node_id = Tree.preorder tree node in
222         let summary = Tree.summary tree node in
223         let fc = Tree.first_child tree node in
224         let ns = Tree.next_sibling tree node in
225         (* We enter the node from its parent *)
226         let status0 = unsafe_get run_sat node_id in
227         (* get the node_statuses for the first child, next sibling and parent *)
228         (* evaluate the transitions with all this statuses *)
229         let action  =
230           eval_trans run
231             run.td_cache tag
232             summary
233             (unsafe_get run_sat (Tree.preorder tree fc))
234             (unsafe_get run_sat (Tree.preorder tree ns))
235             parent_sat
236             status0 td_todo action_builder
237         in
238         action node node_id fc ns
239       end
240
241     and td_action_builder parent_sat summary tag status1 =
242       let update_res = mk_update_res false status1 in
243       match NodeSummary.(has_left summary, has_right summary) with
244         false, false ->
245         (fun node node_id fc ns ->
246            unsafe_set run_sat node_id status1;
247            update_res node;
248            StateSet.empty)
249       | true, false ->
250         (fun node node_id fc ns ->
251            unsafe_set run_sat node_id status1;
252            update_res node;
253            loop_td fc node status1)
254       | false, true ->
255         (fun node node_id fc ns ->
256            unsafe_set run_sat node_id status1;
257            update_res node;
258            loop_td ns node status1)
259       | _ ->
260         (fun node node_id fc ns ->
261            unsafe_set run_sat node_id status1; (* write the td_states *)
262            update_res node;
263            ignore (loop_td fc node status1);
264            loop_td ns node status1 (* tail call *)
265         )
266     and td_and_bu_action_builder parent_sat summary tag status1  =
267       match NodeSummary.(has_left summary, has_right summary) with
268         false, false ->
269         (fun node node_id fc ns ->
270            let action =
271              eval_trans run run.bu_cache tag summary StateSet.empty StateSet.empty
272                parent_sat status1 bu_todo bu_action_builder
273            in
274            action node node_id)
275       | true, false ->
276         (fun node node_id fc ns ->
277            let fcs1 = loop_td_and_bu fc node status1 in
278            let action =
279              eval_trans run run.bu_cache tag summary fcs1 StateSet.empty
280                parent_sat status1 bu_todo bu_action_builder
281            in
282            action node node_id
283         )
284       | false, true ->
285         (fun node node_id fc ns ->
286            let nss1 = loop_td_and_bu ns node status1 in
287            let action =
288              eval_trans run run.bu_cache tag summary StateSet.empty nss1
289                parent_sat status1 bu_todo bu_action_builder
290            in
291            action node node_id
292         )
293       | _ ->
294         (fun node node_id fc ns ->
295            let fcs1 = loop_td_and_bu fc node status1 in
296            let nss1 = loop_td_and_bu ns node status1 in
297            let action =
298              eval_trans run run.bu_cache tag summary fcs1 nss1 parent_sat status1 bu_todo bu_action_builder
299            in
300            action node node_id
301         )
302     and bu_action_builder parent_sat summary tag status2 node node_id =
303       unsafe_set run_sat node_id status2;
304       status2
305     and td_and_bu_last_action_builder parent_sat summary tag status1 =
306       match NodeSummary.(has_left summary, has_right summary) with
307         false, false ->
308         (fun node node_id fc ns ->
309            let action =
310              eval_trans run run.bu_cache tag summary StateSet.empty StateSet.empty
311                parent_sat status1 bu_todo bu_last_action_builder
312            in
313            action node node_id)
314       | true, false ->
315         (fun node node_id fc ns ->
316            let fcs1 = loop_td_and_bu_last fc node status1 in
317            let action =
318              eval_trans run run.bu_cache tag summary fcs1 StateSet.empty
319                parent_sat status1 bu_todo bu_last_action_builder
320            in
321            action node node_id
322         )
323       | false, true ->
324         (fun node node_id fc ns ->
325            let nss1 = loop_td_and_bu_last ns node status1 in
326            let action =
327              eval_trans run run.bu_cache tag summary StateSet.empty nss1
328                parent_sat status1 bu_todo bu_last_action_builder
329            in
330            action node node_id
331         )
332       | _ ->
333         (fun node node_id fc ns ->
334            let nss1 = loop_td_and_bu_last ns node status1 in
335            let fcs1 = loop_td_and_bu_last fc node status1 in
336            let action =
337              eval_trans run run.bu_cache tag summary fcs1 nss1 parent_sat status1 bu_todo bu_last_action_builder
338            in
339            action node node_id
340         )
341     and bu_last_action_builder parent_sat summary tag status2 =
342       let update_res = mk_update_res true status2 in
343       (fun node node_id ->
344          unsafe_set run_sat node_id status2;
345          update_res node;
346          status2)
347     and loop_td node parent parent_sat =
348       common node parent parent_sat td_action_builder
349     and loop_td_and_bu node parent parent_sat =
350       common node parent parent_sat td_and_bu_action_builder
351     and loop_td_and_bu_last node parent parent_sat =
352       common node parent parent_sat td_and_bu_last_action_builder
353     in
354     let _ =
355       if bu_todo == StateSet.empty then
356         loop_td (Tree.root tree) Tree.nil dummy_set
357       else if last_run then
358         loop_td_and_bu_last (Tree.root tree) Tree.nil dummy_set
359       else
360         loop_td_and_bu (Tree.root tree) Tree.nil dummy_set
361     in
362     run.pass <- run.pass + 2;
363     run.stats.pass <- run.stats.pass + 1;
364     run.stats.nodes_per_run <- !num_visited :: run.stats.nodes_per_run
365
366
367
368   let mk_update_result auto =
369     let sel_states = Ata.get_selecting_states auto in
370     let res = ResultSet.create () in
371     (fun prepend sat ->
372        if StateSet.intersect sat sel_states then
373          if prepend then (fun n -> ResultSet.push_front n res)
374          else (fun n -> ResultSet.push_back n res)
375        else (fun _ -> ())),
376     (fun () -> res)
377
378
379   let mk_update_full_result auto =
380     let sel_states = Ata.get_selecting_states auto in
381     let res_mapper =
382       StateSet.fold_right (fun q acc -> (q, ResultSet.create())::acc) sel_states []
383     in
384     (fun prepend sat ->
385        StateSet.fold (fun q f_acc ->
386            if StateSet.mem q sel_states then
387              let res = List.assoc q res_mapper in
388              if prepend then (fun n -> ResultSet.push_front n res; f_acc n)
389              else (fun n -> ResultSet.push_back n res; f_acc n)
390            else f_acc) sat (fun _ -> ())),
391     (fun () -> res_mapper)
392
393   let prepare_run run list =
394     let tree = run.tree in
395     let auto = run.auto in
396     let sat = IFHTML((List.hd run.sat), run.sat) in
397     let sat0 = Ata.get_starting_states auto in
398    ResultSet.iter (fun node ->
399       let node_id = Tree.preorder tree node in
400       sat.(node_id) <- sat0) list
401
402
403   let compute_run auto tree nodes mk_update_res =
404     let run = make auto tree in
405     prepare_run run nodes;
406     let rank = Ata.get_max_rank auto in
407     while run.pass <= rank do
408       top_down run mk_update_res;
409       IFHTML((run.sat <- (Array.copy (List.hd run.sat)) :: run.sat), ());
410       run.td_cache <- Cache.N6.create dummy_action;
411       run.bu_cache <- Cache.N6.create dummy_action;
412     done;
413     IFHTML((run.sat <- List.tl run.sat), ());
414     IFHTML(Html_trace.gen_trace auto run.sat (module T : Tree.S with type t = Tree.t) tree ,());
415     run
416
417
418   let last_stats = ref None
419
420   let full_eval auto tree nodes =
421     let mk_update_full,get_full = mk_update_full_result auto in
422     let run = compute_run auto tree nodes mk_update_full in
423     last_stats := Some run.stats;
424     get_full ()
425
426   let eval auto tree nodes =
427     let mk_update_res,get_res = mk_update_result auto in
428     let run = compute_run auto tree nodes mk_update_res in
429     last_stats := Some run.stats;
430     get_res ()
431
432   let stats () = match !last_stats with
433       Some s -> s.nodes_per_run <- List.rev s.nodes_per_run;s
434     | None -> failwith "Missing stats"
435
436 end