Add a 'trace' mode (must be enabled at build time) that saves the
[tatoo.git] / src / auto / eval.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 (*
17   Time-stamp: <Last modified on 2013-03-14 19:13:55 CET by Kim Nguyen>
18 *)
19
20 INCLUDE "utils.ml"
21 open Format
22 open Utils
23
24 module Make (T : Tree.Sig.S) :
25   sig
26     val eval : Ata.t -> T.t -> T.node -> T.node list
27   end
28  = struct
29
30
31 IFDEF HTMLTRACE
32   THEN
33 DEFINE TRACE(e) = (e)
34   ELSE
35 DEFINE TRACE(e) = ()
36 END
37
38
39
40   type cache = StateSet.t Cache.N1.t
41   let get c t n = Cache.N1.find c (T.preorder t n)
42
43   let set c t n v = Cache.N1.add c (T.preorder t n) v
44
45   module Info = struct
46     type t = { is_left : bool;
47                is_right : bool;
48                has_left : bool;
49                has_right : bool;
50                kind : Tree.Common.NodeKind.t;
51              }
52     let equal a b = a = b
53     let hash  a = Hashtbl.hash a
54   end
55
56   module NodeInfo = Hcons.Make(Info)
57
58   let eval_form phi node_info fcs nss ps ss =
59     let open NodeInfo in
60     let open Info in
61     let rec loop phi =
62       begin match Ata.SFormula.expr phi with
63         Formula.True -> true
64       | Formula.False -> false
65       | Formula.Atom a ->
66           let p, b, q = Ata.Atom.node a in
67           let pos =
68             let open Ata in
69                 match p with
70                 | First_child -> StateSet.mem q fcs
71                 | Next_sibling ->  StateSet.mem q nss
72                 | Parent | Previous_sibling -> StateSet.mem q ps
73                 | Stay -> StateSet.mem q ss
74                 | Is_first_child -> node_info.node.is_left
75                 | Is_next_sibling -> node_info.node.is_right
76                 | Is k -> k == node_info.node.kind
77                 | Has_first_child -> node_info.node.has_left
78                 | Has_next_sibling -> node_info.node.has_right
79             in
80             if Ata.is_move p && (not b) then
81               eprintf "Warning: Invalid negative atom %a" Ata.Atom.print a;
82             b == pos
83       | Formula.And(phi1, phi2) -> loop phi1 && loop phi2
84       | Formula.Or (phi1, phi2) -> loop phi1 || loop phi2
85       end
86     in
87     loop phi
88
89   let eval_trans cache ltrs node_info fcs nss ps ss =
90     let j = (node_info.NodeInfo.id :> int)
91     and k = (fcs.StateSet.id :> int)
92     and l = (nss.StateSet.id :> int)
93     and m = (ps.StateSet.id :> int) in
94   let rec loop ltrs ss =
95     let i = (ltrs.Ata.TransList.id :> int)
96     and n = (ss.StateSet.id :> int) in
97     let (new_ltrs, new_ss) as res =
98       let res = Cache.N6.find cache i j k l m n in
99       if res == Cache.N6.dummy cache then
100         let res =
101           Ata.TransList.fold (fun trs (acct, accs) ->
102             let q, _, phi = Ata.Transition.node trs in
103             if StateSet.mem q accs then (acct, accs) else
104               if eval_form phi node_info fcs nss ps accs then
105                 (acct, StateSet.add q accs)
106               else
107                 (Ata.TransList.cons trs acct, accs)
108           ) ltrs (Ata.TransList.nil, ss)
109         in
110         Cache.N6.add cache i j k l m n res; res
111       else
112         res
113     in
114     if new_ss == ss then res else
115       loop new_ltrs new_ss
116   in
117   loop ltrs ss
118
119   let top_down_run auto tree node cache trans_cache2 trans_cache6  _i =
120     let redo = ref false in
121     let rec loop node =
122       if node != T.nil then begin
123         let parent = T.parent tree node in
124         let fc = T.first_child tree node in
125         let ns = T.next_sibling tree node in
126         let tag = T.tag tree node in
127         let states0 = get cache tree node in
128         let trans0 =
129           let trs =
130             Cache.N2.find trans_cache2
131               (tag.QName.id :> int) (auto.Ata.states.StateSet.id :> int)
132           in
133           if trs == Cache.N2.dummy trans_cache2 then
134             let trs = Ata.get_trans auto auto.Ata.states tag in
135             (Cache.N2.add
136               trans_cache2
137               (tag.QName.id :> int)
138               (auto.Ata.states.StateSet.id :> int) trs; trs)
139           else trs
140         in
141         let () =
142           TRACE(Html.trace (T.preorder tree node) _i "Pre States: %a<br/>Pre Trans: %a<br/>"
143                   StateSet.print states0 Ata.TransList.print trans0)
144         in
145         let ps = get cache tree parent in
146         let fcs = get cache tree fc in
147         let nss = get cache tree ns in
148         let node_info = NodeInfo.make
149           (Info.({ is_left = node == T.first_child tree parent;
150                    is_right = node == T.next_sibling tree parent;
151                    has_left = fc != T.nil;
152                    has_right = ns != T.nil;
153                    kind = T.kind tree node }))
154         in
155         let trans1, states1 =
156           eval_trans trans_cache6 trans0 node_info fcs nss ps states0
157         in
158         let () =
159           TRACE(Html.trace (T.preorder tree node) _i "TD States: %a<br/>TD Trans: %a<br/>" StateSet.print states1 Ata.TransList.print trans1)
160         in
161         if states1 != states0 then set cache tree node states1;
162         let () = loop fc in
163         let fcs1 = get cache tree fc in
164         let trans2, states2 =
165           eval_trans trans_cache6 trans1 node_info fcs1 nss ps states1
166         in
167         let () =
168           TRACE(Html.trace (T.preorder tree node) _i "Left BU States: %a<br/>Left BU Trans: %a<br/>" StateSet.print states2 Ata.TransList.print trans2)
169         in
170         if states2 != states1 then set cache tree node states2;
171         let () = loop ns in
172         let _trans3, states3 =
173           eval_trans trans_cache6 trans2 node_info fcs1 (get cache tree ns) ps states2
174         in
175         let () =
176           TRACE(Html.trace (T.preorder tree node) _i "Right BU States: %a<br/>Right BU Trans: %a<br/>" StateSet.print states3 Ata.TransList.print _trans3)
177         in
178         if states3 != states2 then set cache tree node states3;
179         if states0 != states3 && (not !redo) then redo := true
180       end
181     in
182     loop node;
183     !redo
184
185   let get_results auto tree node cache =
186     let rec loop node acc =
187       if node == T.nil then acc
188       else
189         let acc0 = loop (T.next_sibling tree node) acc in
190         let acc1 = loop (T.first_child tree node) acc0 in
191
192         if StateSet.intersect (get cache tree node) auto.Ata.selection_states then
193           node::acc1
194         else
195           acc1
196     in
197     loop node []
198
199   let eval auto tree node =
200     let cache = Cache.N1.create StateSet.empty in
201     let redo = ref true in
202     let iter = ref 0 in
203     let dummy2 = Ata.TransList.cons
204       (Ata.Transition.make (State.dummy,QNameSet.empty, Ata.SFormula.false_))
205       Ata.TransList.nil
206     in
207     let dummy6 = (dummy2, StateSet.empty) in
208     let trans_cache6 = Cache.N6.create dummy6 in
209     let trans_cache2 = Cache.N2.create dummy2 in
210     let () = at_exit (fun () ->
211       let num_phi = ref 0 in
212       let num_trans = ref 0 in
213       Cache.N6.iteri (fun _ _ _ _ _ _ _ b  -> if not b then incr num_phi) trans_cache6;
214       Cache.N2.iteri (fun _ _ _ b -> if not b then incr num_trans) trans_cache2;
215       Format.eprintf "PROFILE:materialized %i transitions and %i configurations\n@." !num_trans !num_phi
216     )
217     in
218     while !redo do
219       redo := top_down_run auto tree node cache trans_cache2 trans_cache6 !iter;
220       incr iter;
221     done;
222     let r = get_results auto tree node cache in
223     TRACE(Html.gen_trace (module T : Tree.Sig.S with type t = T.t) (tree));
224     r
225
226 end